1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%%%----------------------------------------------------------------
21%%% Purpose:Test Suite for the 'qlc' module.
22%%%-----------------------------------------------------------------
23-module(qlc_SUITE).
24
25-define(QLC, qlc).
26-define(QLCs, "qlc").
27
28%%-define(debug, true).
29
30%% There are often many tests per testcase. Most tests are copied to a
31%% module, a file. The file is compiled and the test run. Should the
32%% test fail, the module file is not removed from ?privdir, but is
33%% kept for inspection. The name of the file is
34%% ?privdir/qlc_test_CASE.erl.
35-define(TESTMODULE, qlc_test).
36-define(TESTCASE, testcase_name).
37
38-ifdef(debug).
39-define(line, put(line, ?LINE), ).
40-define(config(X,Y), foo).
41-define(datadir, ?QLCs ++  "_SUITE_data").
42-define(privdir, ?QLCs ++ "_SUITE_priv").
43-define(testcase, current_testcase). % don't know
44-define(t, test_server).
45-else.
46-include_lib("common_test/include/ct.hrl").
47-define(datadir, proplists:get_value(data_dir, Config)).
48-define(privdir, proplists:get_value(priv_dir, Config)).
49-define(testcase, proplists:get_value(?TESTCASE, Config)).
50-endif.
51
52-include_lib("stdlib/include/ms_transform.hrl").
53
54-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
55	 init_per_group/2,end_per_group/2,
56	 init_per_testcase/2, end_per_testcase/2]).
57
58-export([
59	  badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
60	  filter_var/1, single/1, exported_var/1, generator_vars/1,
61	  nomatch/1, errors/1, pattern/1, overridden_bif/1,
62
63	  eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
64	  evaluator/1, string_to_handle/1, table/1, process_dies/1,
65	  sort/1, keysort/1, filesort/1, cache/1, cache_list/1, filter/1,
66	  info/1, nested_info/1, lookup1/1, lookup2/1, lookup_rec/1,
67	  indices/1, pre_fun/1, skip_filters/1,
68
69	  ets/1, dets/1,
70
71	  join_option/1, join_filter/1, join_lookup/1, join_merge/1,
72	  join_sort/1, join_complex/1,
73
74	  otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1,
75	  otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1,
76	  otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1, otp_11758/1,
77          otp_12946/1,
78
79	  manpage/1,
80
81	  backward/1, forward/1,
82
83	  eep37/1]).
84
85%% Internal exports.
86-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
87         bad_table_format/1, bad_table_format_arity/1, bad_table_traverse/1,
88         bad_table_post/1, bad_table_lookup/1, bad_table_max_lookup/1,
89         bad_table_info_arity/1, bad_table_info_fun_n_objects/1,
90         bad_table_info_fun_indices/1, bad_table_info_fun_keypos/1,
91         bad_table_key_equality/1]).
92-export([evaluator_2/2]).
93-export([prep_scratchdir/1, truncate_tmpfile/2, crash/2, crash_tmpfile/2]).
94-export([etsc/2, etsc/3, create_ets/2, lookup_keys/1]).
95-export([strip_qlc_call/1, join_info/1, join_info_count/1]).
96-export([i/1, i/2, format_info/2]).
97
98-export([table_kill_parent/2, table_parent_throws/2,
99         table_parent_exits/2, table_bad_parent_fun/2]).
100-export([table/2, table/3, stop_list/2, table_error/2, table_error/3,
101         table_lookup_error/1]).
102
103%% error_logger
104-export([install_error_logger/0, uninstall_error_logger/0,
105         read_error_logger/0]).
106-export([init/1,
107	 handle_event/2, handle_call/2, handle_info/2,
108	 terminate/2]).
109
110init_per_testcase(Case, Config) ->
111    [{?TESTCASE, Case} | Config].
112
113end_per_testcase(_Case, _Config) ->
114    ok.
115
116suite() ->
117    [{ct_hooks,[ts_install_cth]},
118     {timetrap,{minutes,5}}].
119
120all() ->
121    [{group, parse_transform}, {group, evaluation},
122     {group, table_impls}, {group, join}, {group, tickets},
123     manpage, {group, compat}].
124
125groups() ->
126    [{parse_transform, [],
127      [badarg, nested_qlc, unused_var, lc, fun_clauses,
128       filter_var, single, exported_var, generator_vars,
129       nomatch, errors, pattern, overridden_bif]},
130     {evaluation, [],
131      [eval, cursor, fold, eval_unique, eval_cache, append,
132       evaluator, string_to_handle, table, process_dies, sort,
133       keysort, filesort, cache, cache_list, filter, info,
134       nested_info, lookup1, lookup2, lookup_rec, indices,
135       pre_fun, skip_filters, eep37]},
136     {table_impls, [], [ets, dets]},
137     {join, [],
138      [join_option, join_filter, join_lookup, join_merge,
139       join_sort, join_complex]},
140     {tickets, [],
141      [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562,
142       otp_6590, otp_6673, otp_6964, otp_7114, otp_7232,
143       otp_7238, otp_7552, otp_6674, otp_7714, otp_11758, otp_12946]},
144     {compat, [], [backward, forward]}].
145
146init_per_suite(Config) ->
147    Config.
148
149end_per_suite(_Config) ->
150    ok.
151
152init_per_group(_GroupName, Config) ->
153    Config.
154
155end_per_group(_GroupName, Config) ->
156    Config.
157
158badarg(Config) when is_list(Config) ->
159    Ts =
160	[{badarg,
161	  <<"-import(qlc, [q/1, q/2]).
162          q(_, _, _) -> ok.
163
164badarg() ->
165    qlc:q(foo),
166    qlc:q(foo, cache_all),
167    qlc:q(foo, cache_all, extra),
168    q(bar),
169    q(bar, cache_all),
170    q(bar, cache_all, extra).
171">>,
172       [],
173{errors,[{5,?QLC,not_a_query_list_comprehension},
174	 {6,?QLC,not_a_query_list_comprehension},
175	 {8,?QLC,not_a_query_list_comprehension},
176	 {9,?QLC,not_a_query_list_comprehension}],
177 []}}],
178    [] = compile(Config, Ts),
179    ok.
180
181%% Nested qlc expressions.
182nested_qlc(Config) when is_list(Config) ->
183    %% Nested QLC expressions. X is bound before the first one; Z and X
184    %% before the second one.
185    Ts =
186     [{nested_qlc1,
187       <<"nested_qlc() ->
188              X = 3, % X unused
189              Q = qlc:q([Y ||
190                            X <- % X shadowed
191                                begin Z = 3,
192                                      qlc:q([Y ||
193                                                Y <- [Z],
194                                                X <- [1,2,3], % X shadowed
195                                                X < Y])
196                                end,
197                            Y <-
198                                [y],
199                            Y > X]),
200              [y, y] = qlc:e(Q),
201              ok.
202       ">>,
203       [warn_unused_vars],
204       {warnings,[{{2,15},erl_lint,{unused_var,'X'}},
205                  {{4,29},erl_lint,{shadowed_var,'X',generate}},
206                  {{8,49},erl_lint,{shadowed_var,'X',generate}}]}},
207
208      {nested_qlc2,
209      <<"nested_qlc() ->
210             H0 = qlc:append([a,b], [c,d]),
211             qlc:q([{X,Y} ||
212                       X <- H0,
213                       Y <- qlc:q([{X,Y} ||
214                                      X <- H0, % X shadowed
215                                      Y <- H0])]),
216             ok.
217       ">>,
218       [warn_unused_vars],
219       {warnings,[{{6,39},erl_lint,{shadowed_var,'X',generate}}]}}
220    ],
221    [] = compile(Config, Ts),
222    ok.
223
224%% Unused variable with a name that should not be introduced.
225unused_var(Config) when is_list(Config) ->
226    Ts =
227     [{unused_var,
228       <<"unused_var() ->
229              qlc:q([X || begin Y1 = 3, true end, % Y1 unused
230                          Y <- [1,2,3],
231                          X <- [a,b,c],
232                          X < Y]).
233       ">>,
234       [warn_unused_vars],
235       {warnings,[{{2,33},erl_lint,{unused_var,'Y1'}}]}}],
236    [] = compile(Config, Ts),
237    ok.
238
239%% Ordinary LC expression.
240lc(Config) when is_list(Config) ->
241    Ts =
242     [{lc,
243       <<"lc() ->
244              [X || X <- [], X <- X]. % X shadowed
245        ">>,
246       [],
247       {warnings,[{{2,30},erl_lint,{shadowed_var,'X',generate}}]}}],
248    [] = compile(Config, Ts),
249    ok.
250
251%% Fun with several clauses.
252fun_clauses(Config) when is_list(Config) ->
253    Ts =
254     [{fun_clauses,
255       <<"fun_clauses() ->
256            {X,X1,X2} = {1,2,3},
257            F = fun({X}) -> qlc:q([X || X <- X]); % X shadowed (fun, generate)
258                   ([X]) -> qlc:q([X || X <- X])  % X shadowed (fun, generate)
259                end,
260            {F,X,X1,X2}.
261        ">>,
262       [],
263       {warnings,[{{3,22},erl_lint,{shadowed_var,'X','fun'}},
264                  {{3,41},erl_lint,{shadowed_var,'X',generate}},
265                  {{4,22},erl_lint,{shadowed_var,'X','fun'}},
266                  {{4,41},erl_lint,{shadowed_var,'X',generate}}]}}],
267    [] = compile(Config, Ts),
268    ok.
269
270%% Variable introduced in filter.
271filter_var(Config) when is_list(Config) ->
272    Ts =
273     [{filter_var,
274       <<"filter_var() ->
275              qlc:q([X ||
276                  Y <- [X ||
277                           X <- [1,2,3]],
278                  begin X = Y, true end]).
279        ">>,
280       [],
281       []},
282
283      {unsafe_filter_var,
284       <<"unsafe_filter_var() ->
285              qlc:q([{X,V} || X <- [1,2],
286                  case {a} of
287                      {_} ->
288                          true;
289                      V ->
290                          V
291                  end]).
292        ">>,
293       [],
294       {errors,[{{2,25},erl_lint,{unsafe_var,'V',{'case',{3,19}}}}],[]}}],
295    [] = compile(Config, Ts),
296    ok.
297
298
299%% Unused pattern variable.
300single(Config) when is_list(Config) ->
301    Ts =
302     [{single,
303       <<"single() ->
304              qlc:q([X || {X,Y} <- [{1,2}]]), % Y unused
305              qlc:q([[] || [] <- [[]]]).
306        ">>,
307       [warn_unused_vars],
308       {warnings,[{{2,30},erl_lint,{unused_var,'Y'}}]}}],
309    [] = compile(Config, Ts),
310    ok.
311
312%% Exported variable in list expression (rhs of generator).
313exported_var(Config) when is_list(Config) ->
314    Ts =
315     [{exported_var,
316       <<"exported() ->
317              qlc:q([X || X <- begin
318                                   case foo:bar() of
319                                       1 -> Z = a;
320                                       2 -> Z = b
321                                   end,
322                                   [Z = 3, Z = 3] % Z exported (twice...)
323                               end
324                         ]).
325       ">>,
326       [warn_export_vars],
327       {warnings,[{{7,37},erl_lint,{exported_var,'Z',{'case',{3,36}}}},
328                  {{7,44},erl_lint,{exported_var,'Z',{'case',{3,36}}}}]}}],
329    [] = compile(Config, Ts),
330    ok.
331
332%% Errors for generator variable used in list expression.
333generator_vars(Config) when is_list(Config) ->
334    Ts =
335      [{generator_vars,
336        <<"generator_vars() ->
337               qlc:q([X ||
338                      Z <- [1,2],
339                      X <- begin
340                               case 1 of
341                                   1 -> Z = a; % used_generator_variable
342                                   2 -> Z = b % used_generator_variable
343                               end,
344                               [Z = 3, Z = 3] % used_generator_variable (2)
345                           end
346                     ]).
347        ">>,
348        [],
349        {errors,[{{6,41},?QLC,{used_generator_variable,'Z'}},
350                 {{7,41},?QLC,{used_generator_variable,'Z'}},
351                 {{9,33},?QLC,{used_generator_variable,'Z'}},
352                 {{9,40},?QLC,{used_generator_variable,'Z'}}],
353         []}}],
354    [] = compile(Config, Ts),
355    ok.
356
357%% Unreachable clauses also found when compiling.
358nomatch(Config) when is_list(Config) ->
359    Ts =
360      [{unreachable1,
361        <<"unreachable1() ->
362               qlc:q([X || X <- [1,2],
363                   case X of
364                       true -> false;
365                       true -> true   % clause cannot match
366                    end]).
367        ">>,
368        [],
369        {warnings,[{5,v3_kernel,{nomatch_shadow,4}}]}},
370
371       {nomatch1,
372        <<"generator1() ->
373              qlc:q([3 || {3=4} <- []]).
374        ">>,
375        [],
376        %% {warnings,[{{2,27},qlc,nomatch_pattern}]}},
377        {warnings,[{2,v3_core,nomatch}]}},
378
379       {nomatch2,
380        <<"nomatch() ->
381                etsc(fun(E) ->
382                Q = qlc:q([3 || {3=4} <- ets:table(E)]),
383                [] = qlc:eval(Q),
384                false = lookup_keys(Q)
385          end, [{1},{2}]).
386        ">>,
387        [],
388        %% {warnings,[{{3,33},qlc,nomatch_pattern}]}},
389        {warnings,[{3,v3_core,nomatch}]}},
390
391       {nomatch3,
392        <<"nomatch() ->
393              etsc(fun(E) ->
394                          Q = qlc:q([{A,B,C,D} || A=B={C=D}={_,_} <-
395                                                    ets:table(E)]),
396                          [] = qlc:eval(Q),
397                          false = lookup_keys(Q)
398                    end, [{1,2},{2,3}]).
399        ">>,
400        [],
401        %% {warnings,[{{3,52},qlc,nomatch_pattern}]}},
402        {warnings,[{3,v3_core,nomatch}]}},
403
404       {nomatch4,
405        <<"nomatch() ->
406              etsc(fun(E) ->
407                          Q = qlc:q([{X,Y} || {<<X>>} = {<<Y>>} <-
408                                                    ets:table(E)]),
409                          [] = qlc:eval(Q),
410                          false = lookup_keys(Q)
411                    end, [{<<34>>},{<<40>>}]).
412        ">>,
413        [],
414        {errors,[{{3,48},erl_lint,illegal_bin_pattern}],[]}},
415
416       {nomatch5,
417        <<"nomatch() ->
418               etsc(fun(E) ->
419                           Q = qlc:q([t || {\"a\"++\"b\"} = {\"ac\"} <-
420                                                    ets:table(E)]),
421                           [t] = qlc:eval(Q),
422                           [\"ab\"] = lookup_keys(Q)
423                     end, [{\"ab\"}]).
424        ">>,
425        [],
426        {warnings,[{3,v3_core,nomatch}]}}
427
428      ],
429    [] = compile(Config, Ts),
430    ok.
431
432
433%% Errors within qlc expressions also found when compiling.
434errors(Config) when is_list(Config) ->
435    Ts =
436      [{errors1,
437        <<"errors1() ->
438               qlc:q([X || X <- A]). % A unbound
439        ">>,
440        [],
441        {errors,[{{2,33},erl_lint,{unbound_var,'A'}}],[]}}],
442    [] = compile(Config, Ts),
443    ok.
444
445%% Patterns.
446pattern(Config) when is_list(Config) ->
447    Ts = [
448      <<"%% Records in patterns. No lookup.
449         L = [#a{k=#k{v=91}}],
450         H = qlc:q([Q || Q = #a{k=#k{v=91}} <- qlc_SUITE:table(L, 2, [])]),
451         {qlc,_,[{generate,_,{table,{call,_,_,_}}}], []} = i(H),
452         L = qlc:e(H),
453         {call, _, _q, [{lc,_,{var,_,'Q'},
454                         [{generate,_,
455                           {match,_,_,_},
456                           {call,_,_,_}}]}]}
457              = i(H, {format,abstract_code})">>,
458
459      <<"%% No matchspec since there is a binary in the pattern.
460         etsc(fun(E) ->
461             Q = qlc:q([A || {<<A:3/unit:8>>} <- ets:table(E)]),
462             [_] = qlc:eval(Q),
463             {qlc,_,[{generate,_,{table,_}}], []} = i(Q)
464         end, [{<<\"hej\">>}])">>
465
466       ],
467    run(Config, <<"-record(a, {k,v}).
468                         -record(k, {t,v}).\n">>, Ts),
469    ok.
470
471%% Override a guard BIF with an imported or local function.
472overridden_bif(Config) ->
473    Ts = [
474	  <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])),
475             [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12],
476                                      (is_reference(P) andalso P > 5)])),
477             Empty = gb_sets:empty(), Single = gb_sets:singleton(42),
478             GbSets = [Empty,Single],
479             [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0]))
480            ">>
481	 ],
482    run(Config, "-import(gb_sets, [size/1]).
483                 -compile({no_auto_import, [size/1, is_reference/1]}).
484                 port(N) -> N rem 2 =:= 0.
485                 is_reference(N) -> N rem 10 =:= 0.\n", Ts),
486    ok.
487
488
489%% eval/2
490eval(Config) when is_list(Config) ->
491    ScratchDir = filename:join([?privdir, "scratch","."]),
492
493    Ts = [<<"{'EXIT',{badarg,_}} = (catch qlc:eval(not_a_qlc)),
494             H = qlc:q([X || X <- [1,2]]),
495             {'EXIT',{{unsupported_qlc_handle,{qlc_handle,foo}},_}}=
496                       (catch qlc:e({qlc_handle,foo})),
497             {'EXIT',{badarg,_}} = (catch qlc:eval(H, [{unique_all,badarg}])),
498             {'EXIT',{badarg,_}} =
499                      (catch qlc:eval(H, [{spawn_options,badarg}])),
500             {'EXIT',{badarg,_}} =
501                      (catch qlc:eval(H, [{unique_all,true},{bad,arg}])),
502             {throw,t} =
503                (catch {any_term,qlc:e(qlc:q([X || X <- throw({throw,t})]))}),
504             M = qlc,
505             {'EXIT',{badarg,_}} = (catch M:q(bad))">>,
506
507          [<<"Dir = \"">>,ScratchDir,<<"\",
508              qlc_SUITE:prep_scratchdir(Dir),
509
510              E = ets:new(foo, []),
511              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
512              H = qlc:q([{X,Y} || Y <- [1,2],
513                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
514                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
515              R = qlc:eval(H),
516              ets:delete(E),
517              {error,_,{bad_object,_}} = R,
518              \"the tempo\" ++ _ = lists:flatten(qlc:format_error(R))">>],
519
520          [<<"Dir = \"">>,ScratchDir,<<"\",
521              qlc_SUITE:prep_scratchdir(Dir),
522
523              E = ets:new(foo, []),
524              Bin = term_to_binary(lists:seq(1,20000)),
525              [true || I <- lists:seq(1, 10), not ets:insert(E, {I, I, Bin})],
526              H = qlc:q([{X,Y} || Y <- [1,2],
527                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
528                                  qlc_SUITE:crash_tmpfile(Dir, 5)]),
529              R = qlc:eval(H),
530              ets:delete(E),
531              {error,_,{bad_object,_}} = R">>],
532
533          <<"E = ets:new(test, []),
534             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
535                                 Y <- ets:table(E)]),
536             R1 = (catch {any_term,qlc:eval(H, {unique_all,false})}),
537             R2 = (catch {any_term,qlc:eval(H, {unique_all,true})}),
538             ets:delete(E),
539             true = {throw,bad_pre_fun} == R1,
540             true = {throw,bad_pre_fun} == R2">>,
541
542          <<"E = ets:new(test, []),
543             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
544                                 Y <- ets:table(E)]),
545             R1 = (catch qlc:eval(H, {unique_all,false})),
546             R2 = (catch qlc:eval(H, {unique_all,true})),
547             ets:delete(E),
548             {'EXIT',{bad_pre_fun,_}} = R1,
549             {'EXIT',{bad_pre_fun,_}} = R2">>,
550
551          <<"Q = qlc:q([X || X <- [4,3,2,1,0,-1], begin 3/X > 0 end]),
552             {'EXIT',{badarith,_}} = (catch qlc:eval(Q, {unique_all,false})),
553             {'EXIT',{badarith,_}} = (catch qlc:eval(Q, {unique_all,true}))
554            ">>,
555
556          <<"[1,2] = qlc:eval(qlc:q([X || X <- [1,2]])),
557             [1,2,3,4] = qlc:eval(qlc:append([1,2],[3,4])),
558             [1,2] = qlc:eval(qlc:sort([2,1])),
559             E = ets:new(foo, []),
560             ets:insert(E, [{1},{2}]),
561             [{1},{2}] = lists:sort(qlc:eval(ets:table(E))),
562             true = ets:delete(E)">>,
563
564          <<"H = qlc:q([X || X <- [1,2],
565                             begin F = fun() ->
566                                qlc:e(qlc:q([Y || Y <- [1,2]])) end,
567                                F() == (fun f/0)() end]),
568             [1,2] = qlc:e(H),
569             ok.
570
571             f() -> [1,2].
572             foo() -> bar">>,
573
574          <<"C1_0_1 = [1,2],
575             %% The PT cannot rename C to C1_0_1; another name is chosen.
576             [1,2] = qlc:eval(qlc:q([C || C <- C1_0_1]))">>,
577
578          <<"H = qlc:q([X || {X,X} <- [{1,a},{2,2},{b,b},{3,4}]]),
579             [2,b] = qlc:e(H),
580             H1 = qlc:q([3 || {X,X} <- [{1,a},{2,2},{b,b},{3,4}]]),
581             [3,3] = qlc:e(H1)">>,
582
583          %% Just to cover a certain line in qlc.erl (avoids returning [])
584          <<"E = ets:new(foo, []),
585             Bin = term_to_binary(lists:seq(1,20000)),
586             [true || I <- lists:seq(1, 10), not ets:insert(E, {I, I, Bin})],
587             H = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:sort(ets:table(E))]),
588             R = qlc:eval(H),
589             ets:delete(E),
590             20 = length(R)">>,
591
592          <<"H = qlc:q([{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||
593                 {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <-
594                  [{a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w}]]),
595             [_] = qlc:e(H)">>,
596
597          <<"H = qlc:q([Y || Y <- [1,2]],
598                       {unique, begin [T] = qlc:e(qlc:q([X || X <- [true]],
599                                                        cache)),
600                                      T end}),
601             [1,2] = qlc:e(H)">>
602
603          ],
604
605    run(Config, Ts),
606    ok.
607
608%% cursor/2
609cursor(Config) when is_list(Config) ->
610    ScratchDir = filename:join([?privdir, "scratch","."]),
611    Ts = [<<"{'EXIT',{badarg,_}} =
612                   (catch qlc:cursor(fun() -> not_a_cursor end)),
613             H0 = qlc:q([X || X <- throw({throw,t})]),
614             {throw,t} = (catch {any_term,qlc:cursor(H0)}),
615             H = qlc:q([X || X <- [1,2]]),
616             {'EXIT',{badarg,_}} =
617                       (catch qlc:cursor(H,{spawn_options, [a|b]})),
618             {'EXIT',{badarg,_}} =
619                       (catch qlc:cursor(H,{bad_option,true}))">>,
620
621          <<"{'EXIT',{badarg,_}} = (catch qlc:delete_cursor(not_a_cursor))">>,
622
623          [<<"Dir = \"">>,ScratchDir,<<"\",
624              qlc_SUITE:prep_scratchdir(Dir), % kludge
625              E = ets:new(foo, []),
626              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
627              H = qlc:q([{X,Y} || begin put('$qlc_tmpdir', true), true end,
628                                  Y <- [1,2],
629                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
630                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
631              C = qlc:cursor(H),
632              R = qlc:next_answers(C, all_remaining),
633              qlc:delete_cursor(C),
634              erase('$qlc_tmpdir'),
635              ets:delete(E),
636              {error,_,{bad_object,_}} = R">>],
637
638          <<"H1 = qlc:q([X || X <- [1,2]]),
639             C1 = qlc:cursor(H1),
640             [1,2] = qlc:next_answers(C1, all_remaining),
641             [] = qlc:next_answers(C1),
642             [] = qlc:next_answers(C1),
643             ok = qlc:delete_cursor(C1),
644
645             H2 = qlc:append([1,2],[3,4]),
646             C2 = qlc:cursor(H2),
647             [1,2,3,4] = qlc:next_answers(C2, all_remaining),
648             ok = qlc:delete_cursor(C2),
649
650             H3 = qlc:sort([2,1]),
651             C3 = qlc:cursor(H3),
652             [1,2] = qlc:next_answers(C3, all_remaining),
653             ok = qlc:delete_cursor(C3),
654
655             E = ets:new(foo, []),
656             ets:insert(E, [{1},{2}]),
657             H4 = ets:table(E),
658             C4 = qlc:cursor(H4),
659             [{1},{2}] = lists:sort(qlc:next_answers(C4, all_remaining)),
660             ok = qlc:delete_cursor(C4),
661             true = ets:delete(E)">>,
662
663          <<"H = qlc:q([{X,Y} || X <- [1,2], Y <- [a,b]]),
664             C = qlc:cursor(H, []),
665             [{1,a},{1,b}] = qlc:next_answers(C, 2),
666             [{2,a}] = qlc:next_answers(C, 1),
667             [{2,b}] = qlc:next_answers(C, all_remaining),
668             {'EXIT',{badarg,_}} = (catch qlc:next_answers(C, -1)),
669             P = self(),
670             Pid1 = spawn_link(fun() ->
671                          {'EXIT',{not_cursor_owner,_}} =
672                                (catch qlc:delete_cursor(C)),
673                          P ! {self(), done} end),
674             Pid2 = spawn_link(fun() ->
675                          {'EXIT',{not_cursor_owner,_}} =
676                                (catch qlc:next_answers(C)),
677                          P ! {self(), done} end),
678             receive {Pid1, done} -> ok end,
679             receive {Pid2, done} -> ok end,
680             ok = qlc:delete_cursor(C),
681             {'EXIT',{badarg,_}} = (catch qlc:next_answers(not_a_cursor)),
682             ok = qlc:delete_cursor(C)">>,
683
684          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
685             C1 = qlc:cursor(Q, [{unique_all,true}]),
686             [1,2] = qlc:next_answers(C1, all_remaining),
687             ok = qlc:delete_cursor(C1),
688             C2 = qlc:cursor(Q, [{unique_all,true}]),
689             [1,2] = qlc:next_answers(C2, all_remaining),
690             ok = qlc:delete_cursor(C2)">>,
691
692          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
693             C1 = qlc:cursor(Q, [{unique_all,true},{spawn_options, []}]),
694             [1,2] = qlc:next_answers(C1, all_remaining),
695             ok = qlc:delete_cursor(C1),
696             C2 = qlc:cursor(Q, [{unique_all,true},{spawn_options, default}]),
697             [1,2] = qlc:next_answers(C2, all_remaining),
698             ok = qlc:delete_cursor(C2)">>,
699
700          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
701             C1 = qlc:cursor(Q, [{unique_all,false},{spawn_options, []}]),
702             [1,2,1,2,1] = qlc:next_answers(C1, all_remaining),
703             ok = qlc:delete_cursor(C1),
704             C2 = qlc:cursor(Q, [{unique_all,false},{spawn_options, []}]),
705             [1,2,1,2,1] = qlc:next_answers(C2, all_remaining),
706             ok = qlc:delete_cursor(C2)">>,
707
708          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
709             C1 = qlc:cursor(Q, [{unique_all,false}]),
710             [1,2,1,2,1] = qlc:next_answers(C1, all_remaining),
711             ok = qlc:delete_cursor(C1),
712             C2 = qlc:cursor(Q, [{unique_all,false}]),
713             [1,2,1,2,1] = qlc:next_answers(C2, all_remaining),
714             ok = qlc:delete_cursor(C2)">>
715
716         ],
717    run(Config, Ts),
718    ok.
719
720%% fold/4
721fold(Config) when is_list(Config) ->
722    ScratchDir = filename:join([?privdir, "scratch","."]),
723    Ts = [<<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
724             F = fun(Obj, A) -> A++[Obj] end,
725             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], Q, {bad,arg})),
726             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], badarg)),
727             {'EXIT',{badarg,_}} =
728               (catch qlc:fold(F, [], {spawn_options, [a|b]})),
729             H = qlc:q([X || X <- throw({throw,t})]),
730             {throw,t} = (catch {any_term,qlc:fold(F, [], H)}),
731             [1,2] = qlc:fold(F, [], Q, {unique_all,true}),
732             {'EXIT',{badarg,_}} =
733               (catch qlc:fold(F, [], Q, [{unique_all,bad}])),
734             [1,2,1,2,1] =
735                  qlc:fold(F, [], Q, [{unique_all,false}])">>,
736
737          [<<"Dir = \"">>,ScratchDir,<<"\",
738              qlc_SUITE:prep_scratchdir(Dir),
739
740              E = ets:new(foo, []),
741              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
742              H = qlc:q([{X,Y} || Y <- [1,2],
743                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
744                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
745              F = fun(Obj, A) -> A++[Obj] end,
746              R = qlc:fold(F, [], H),
747              ets:delete(E),
748              {error,_,{bad_object,_}} = R">>],
749
750          <<"E = ets:new(test, []),
751             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
752                                 Y <- ets:table(E)]),
753             F = fun(Obj, A) -> A++[Obj] end,
754             R1 = (catch {any_term,qlc:fold(F, [], H, {unique_all,false})}),
755             R2 = (catch {any_term,qlc:fold(F, [], H, {unique_all,true})}),
756             ets:delete(E),
757             true = {throw,bad_pre_fun} == R1,
758             true = {throw,bad_pre_fun} == R2">>,
759
760          <<"E = ets:new(test, []),
761             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
762                                 Y <- ets:table(E)]),
763             F = fun(Obj, A) -> A++[Obj] end,
764             R1 = (catch qlc:fold(F, [], H, {unique_all,false})),
765             R2 = (catch qlc:fold(F, [], H, {unique_all,true})),
766             ets:delete(E),
767             {'EXIT',{bad_pre_fun,_}} = R1,
768             {'EXIT',{bad_pre_fun,_}} = R2">>,
769
770          <<"F = fun(Obj, A) -> A++[Obj] end,
771             Q = qlc:q([X || X <- [1,2,1,2,1], throw({throw,wrong})]),
772             {throw,wrong} =
773                 (catch {any_term,qlc:fold(F, [], Q, {unique_all,true})}),
774             {throw,wrong} =
775                 (catch {any_term,qlc:fold(F, [], Q)})">>,
776
777          <<"F = fun(Obj, A) -> A++[Obj] end,
778             Q = qlc:q([X || X <- [4,3,2,1,0,-1], begin 3/X > 0 end]),
779             {'EXIT',{badarith,_}} =
780                       (catch qlc:fold(F, [], Q, {unique_all,true})),
781             {'EXIT',{badarith,_}} =
782                 (catch qlc:fold(F, [], Q, [{unique_all,false}]))
783            ">>,
784
785          <<"F = fun(Obj, A) -> A++[Obj] end,
786             [1,2] = qlc:fold(F, [], qlc:q([X || X <- [1,2]])),
787             [1,2,3,4] = qlc:fold(F, [], qlc:append([1,2],[3,4])),
788             [1,2] = qlc:fold(F, [], qlc:sort([2,1])),
789             E = ets:new(foo, []),
790             ets:insert(E, [{1},{2}]),
791             [{1},{2}] = lists:sort(qlc:fold(F, [], ets:table(E))),
792             true = ets:delete(E)">>,
793
794          <<"F = fun(_Obj, _A) -> throw({throw,fatal}) end,
795             Q = qlc:q([X || X <- [4,3,2]]),
796             {throw,fatal} =
797              (catch {any_term,qlc:fold(F, [], Q, {unique_all,true})}),
798             {throw,fatal} =
799               (catch {any_term,qlc:fold(F, [], Q, [{unique_all,false}])})">>,
800
801          <<"G = fun(_Obj, _A, D) -> 17/D  end,
802             F = fun(Obj, A) -> G(Obj, A, 0) end,
803             Q = qlc:q([X || X <- [4,3,2]]),
804             {'EXIT',{badarith,_}} =
805                    (catch qlc:fold(F, [], Q, {unique_all,true})),
806             {'EXIT',{badarith,_}} =
807               (catch qlc:fold(F, [], Q, [{unique_all,false}]))
808            ">>
809         ],
810    run(Config, Ts),
811    ok.
812
813%% Test the unique_all option of eval.
814eval_unique(Config) when is_list(Config) ->
815    Ts = [<<"QLC1 = qlc:q([X || X <- qlc:append([[1,1,2], [1,2,3,2,3]])]),
816             [1,2,3] = qlc:eval(QLC1, {unique_all,true}),
817             QLC2 = qlc:q([X || X <- [1,2,1,2,1,2,1]]),
818             [1,2] = qlc:e(QLC2, {unique_all,true})">>,
819
820          <<"E = ets:new(test, []),
821             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
822             H = qlc:q([X || X <- qlc:append([ets:table(E), ets:table(E)])]),
823             R1 = qlc:e(H, {unique_all,false}),
824             R2 = qlc:e(H, {unique_all,true}),
825             ets:delete(E),
826             true = lists:sort(R1) == [{1,a},{1,a},{2,b},{2,b},{3,c},{3,c}],
827             true = lists:sort(R2) == [{1,a},{2,b},{3,c}]
828            ">>,
829
830          <<"Q1 = qlc:q([{X,make_ref()} || X <- [1,2,1,2]]),
831             [_,_] = qlc:e(Q1, {unique_all,true}),
832             [_,_,_,_] = qlc:e(Q1, {unique_all,false}),
833             [_,_] = qlc:e(Q1, [{unique_all,true}]),
834             Q2 = qlc:q([{X,make_ref()} || X <- qlc:append([[1,2,1,2]])]),
835             [_,_] = qlc:e(Q2, {unique_all,true}),
836             [_,_,_,_] = qlc:e(Q2, {unique_all,false}),
837             [_,_] = qlc:e(Q2, [{unique_all,true}])
838            ">>,
839
840          <<"Q = qlc:q([{X,make_ref()} || X <- qlc:sort([1,2,1,2])]),
841             [_, _] = qlc:e(Q, {unique_all,true}),
842             Q1 = qlc:q([X || X <- [1,2,1,2]]),
843             Q2 = qlc:q([{X,make_ref()} || X <- qlc:sort(Q1)]),
844             [_, _] = qlc:e(Q2, {unique_all,true})
845            ">>,
846
847          <<"E = ets:new(test, []),
848             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
849             H = qlc:q([X || X <- qlc:append([[1,2,1,2]])]),
850             [1,2,1,2] = qlc:e(H, {unique_all,false}),
851             [1,2] = qlc:e(H, {unique_all,true}),
852             ets:delete(E)">>,
853
854          <<"E = ets:new(foo, [duplicate_bag]),
855             true = ets:insert(E, [{1,a},{1,a},{2,b},{3,c},{4,c},{4,d}]),
856             Q1 = qlc:q([{X,make_ref()} || {_, X} <- ets:table(E)]),
857             true = length(qlc:eval(Q1, {unique_all, true})) =:= 5,
858             Q2 = qlc:q([X || {_, X} <- ets:table(E)]),
859             true = length(qlc:eval(Q2, {unique_all, true})) =:= 4,
860             Q3 = qlc:q([element(2, X) || X <- ets:table(E)]),
861             true = length(qlc:eval(Q3, {unique_all, true})) =:= 4,
862             Q4 = qlc:q([1 || _X <- ets:table(E)]),
863             true = length(qlc:eval(Q4, {unique_all, true})) =:= 1,
864             true = ets:delete(E)
865            ">>,
866
867          <<"Q1 = qlc:q([X || X <- qlc:append([[1], [2,1]])]),
868             Q2 = qlc:q([X || X <- qlc:append([[2,1], [2]])]),
869             Q3 = qlc:q([{X,Y} || X <- Q1, Y <- Q2]),
870             [{1,2},{1,1},{2,2},{2,1}] = qlc:e(Q3, {unique_all,true}),
871             Q4 = qlc:q([{X,Y,make_ref()} || X <- Q1, Y <- Q2]),
872             [{1,2,_},{1,1,_},{2,2,_},{2,1,_}] = qlc:e(Q4, {unique_all,true})
873            ">>,
874
875          <<"Q1 = qlc:q([X || X <- [1,2,1]]),
876             Q2 = qlc:q([X || X <- [2,1,2]]),
877             Q3 = qlc:q([{X,Y} || X <- Q1, Y <- Q2]),
878             [{1,2},{1,1},{2,2},{2,1}] = qlc:e(Q3,{unique_all,true}),
879             Q4 = qlc:q([{X,Y,make_ref()} || X <- Q1, Y <- Q2]),
880             [{1,2,_},{1,1,_},{2,2,_},{2,1,_}] = qlc:e(Q4, {unique_all,true})
881            ">>,
882
883          <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{1,b}]]),
884             [1] = qlc:e(Q1, {unique_all, true}),
885             Q2 = qlc:q([a || _ <- [{1,a},{1,b}]]),
886             [a] = qlc:e(Q2, {unique_all, true})
887            ">>,
888
889          <<"Q = qlc:q([SQV || SQV <- qlc:q([X || X <- [1,2,1,#{a => 1}]],
890                                             unique)],
891                       unique),
892             {call,_,_,[{lc,_,{var,_,'X'},[{generate,_,{var,_,'X'},_}]},_]} =
893                 qlc:info(Q, [{format,abstract_code},unique_all]),
894             [1,2,#{a := 1}] = qlc:e(Q)">>,
895
896          <<"Q = qlc:q([X || X <- [1,2,1]]),
897             {call,_,_,[{lc,_,{var,_,'X'},[{generate,_,{var,_,'X'},_}]},_]} =
898                 qlc:info(Q, [{format,abstract_code},unique_all]),
899             [1,2] = qlc:e(Q, unique_all)">>,
900
901          <<"Q1 = qlc:sort([{1},{2},{3},{1}], [{unique,true}]),
902             Q = qlc:sort(Q1,[{unique,true}]),
903             {sort,{sort,{list,_},[{unique,true}]},[]} = i(Q)">>
904
905         ],
906    run(Config, Ts),
907    ok.
908
909%% Test the cache_all and unique_all options of eval.
910eval_cache(Config) when is_list(Config) ->
911    Ts = [
912       <<"E = ets:new(apa, [ordered_set]),
913          ets:insert(E, [{1},{2}]),
914          H = qlc:q([X || Y <- [3,4],
915                          ets:insert(E, {Y}),
916                          X <- ets:table(E)]), % already unique, no cache...
917          {qlc, _,
918           [{generate, _, {qlc, _,
919                           [{generate, _, {list, [3,4]}}],
920                           [{unique,true}]}},
921            _,
922            {generate, _, {table,_}}],
923           [{unique,true}]} = i(H, [cache_all, unique_all]),
924          [{1},{2},{3},{4}] = qlc:e(H,  [cache_all, unique_all]),
925          ets:delete(E)">>,
926
927       <<"E = ets:new(apa, [ordered_set]),
928          ets:insert(E, [{1},{2}]),
929          H = qlc:q([X || Y <- [3,4],
930                          ets:insert(E, {Y}),
931                          X <- ets:table(E)]), % no cache...
932          {qlc, _,
933           [{generate, _,{list, [3,4]}},
934            _,
935            {generate, _, {table,_}}],
936           []} = i(H, cache_all),
937          [{1},{2},{3},{1},{2},{3},{4}] = qlc:e(H,  [cache_all]),
938          ets:delete(E)">>,
939
940       <<"E = ets:new(apa, [ordered_set]),
941          ets:insert(E, [{1},{2}]),
942          H = qlc:q([X || Y <- [3,4],
943                          ets:insert(E, {Y}),
944                          X <- qlc:q([X || X <- ets:table(E)], cache)]),
945          {qlc, _,
946           [{generate, _, {list, [3,4]}},
947            _,
948            {generate, _, {qlc, _,
949                           [{generate, _, {table,_}}],
950                           [{cache,ets}]}}],
951           []} = i(H, cache_all),
952          [{1},{2},{3},{1},{2},{3}] = qlc:e(H,  [cache_all]),
953          ets:delete(E)">>,
954
955       <<"%% {cache_all,no} does not override {cache,true}.
956          E = ets:new(apa, [ordered_set]),
957          ets:insert(E, [{1},{2}]),
958          H = qlc:q([X || Y <- [3,4],
959                          ets:insert(E, {Y}),
960                          X <- qlc:q([X || X <- ets:table(E)], cache)]),
961          {qlc, _,
962           [{generate, _, {list, [3,4]}},
963            _,
964            {generate, _, {qlc, _,
965                           [{generate, _, {table,_}}],
966                           [{cache,ets}]}}],
967           []} = i(H, {cache_all,no}),
968          [{1},{2},{3},{1},{2},{3}] = qlc:e(H,  [cache_all]),
969          ets:delete(E)">>,
970
971       <<"E = ets:new(apa, [ordered_set]),
972          ets:insert(E, [{1},{2}]),
973          H = qlc:q([X || Y <- [3,4],
974                          ets:insert(E, {Y}),
975                          X <- ets:table(E)]),
976          {qlc, _,
977           [{generate, _, {qlc, _, [{generate, _,{list, [3,4]}}],
978                           [{unique,true}]}},
979            _,
980            {generate, _,{table,_}}],
981           [{unique,true}]} = i(H, unique_all),
982          [{1},{2},{3},{4}] = qlc:e(H, [unique_all]),
983          ets:delete(E)">>,
984
985          %% cache_all is ignored
986       <<"E = ets:new(apa, [ordered_set]),
987          ets:insert(E, [{1},{2},{0}]),
988          H = qlc:q([X || X <- qlc:sort(ets:table(E))]),
989          {sort,_Table,[]} = i(H, cache_all),
990          [{0},{1},{2}] = qlc:e(H, cache_all),
991          ets:delete(E)">>,
992
993       <<"F = fun(Obj, A) -> A++[Obj] end,
994          E = ets:new(apa, [duplicate_bag]),
995          true = ets:insert(E, [{1,a},{2,b},{1,a}]),
996          Q = qlc:q([X || X <- ets:table(E)], cache),
997          {table, _} = i(Q, []),
998          R = qlc:fold(F, [], Q, []),
999          ets:delete(E),
1000          true = [{1,a},{1,a},{2,b}] == lists:sort(R)">>,
1001
1002       <<"E = ets:new(apa, [ordered_set]),
1003          ets:insert(E, [{1},{2},{0}]),
1004          H = qlc:q([X || X <- ets:table(E)], cache),
1005          {table, _} = i(H, cache_all),
1006          [{0},{1},{2}]= qlc:e(H, cache_all),
1007          ets:delete(E)">>,
1008
1009       <<"E = ets:new(foo, []),
1010          true = ets:insert(E, [{1}, {2}]),
1011          Q1 = qlc:q([{X} || X <- ets:table(E)]),
1012          Q2 = qlc:q([{X,Y} || {X} <- Q1, {Y} <- Q1]),
1013          {qlc, _, [{generate, _, {table, _}},
1014                    {generate, _, {qlc, _, [{generate, _, {table, _}}],
1015                                   [{cache,ets}]}}],
1016           []} = i(Q2, cache_all),
1017          [{{1},{1}},{{1},{2}},{{2},{1}},{{2},{2}}] =
1018              lists:sort(qlc:e(Q2, cache_all)),
1019          ets:delete(E)">>,
1020
1021       <<"L1 = [1,2,3],
1022          L2 = [4,5,6],
1023          Q1 = qlc:append(L1, L2),
1024          Q2 = qlc:q([{X} || X <- Q1]),
1025          {qlc, _,[{generate, _,{append, [{list, L1}, {list, L2}]}}], []} =
1026              i(Q2, [cache_all]),
1027          [{1},{2},{3},{4},{5},{6}] = qlc:e(Q2, [cache_all])">>,
1028
1029       <<"H = qlc:sort(qlc:q([1 || _ <- [a,b]])),
1030          {sort, {qlc, _, [{generate, _, {qlc, _, [{generate, _,
1031                                                    {list, [a,b]}}],
1032                                          [{unique,true}]}}],
1033                  [{unique,true}]},
1034                 []} = i(H, unique_all),
1035          [1] = qlc:e(H, unique_all)">>
1036
1037         ],
1038    run(Config, Ts),
1039    ok.
1040
1041%% Test the append function.
1042append(Config) when is_list(Config) ->
1043    Ts = [<<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3], begin 10/X > 0.0 end])),
1044             R = (catch qlc:next_answers(C)),
1045             {'EXIT',{badarith,_}} = R">>,
1046
1047          <<"C = qlc:cursor(qlc:q([X || X <- [0 | fun() -> exit(bad) end]])),
1048             R = (catch qlc:next_answers(C)),
1049             {'EXIT',bad} = R">>,
1050
1051          <<"{'EXIT',{badarg,_}} = (catch qlc:append([a], a)),
1052             {'EXIT',{badarg,_}} = (catch qlc:append([[a],a]))">>,
1053
1054          <<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3],
1055                                     begin throw({throw,wrong}), true end])),
1056             {throw,wrong} = (catch {any_term,qlc:next_answers(C)})">>,
1057
1058          <<"QLC = qlc:q([X || X <- [0,1,2,3],
1059                               begin throw({throw,wrong}), true end]),
1060             {throw,wrong} = (catch {any_term,qlc:eval(QLC)}),
1061             {throw,wrong} =
1062                 (catch {any_term,qlc:e(QLC, {unique_all,true})})">>,
1063
1064          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1065             H2 = qlc:q([X || X <- [4,5,6]]),
1066             R = qlc:e(qlc:q([X || X <- qlc:append([H1, H2])])),
1067             true = R == [1,2,3,4,5,6]">>,
1068
1069          <<"H1 = [1,2,3],
1070             H2 = qlc:q([X || X <- [4,5,6]]),
1071             R = qlc:e(qlc:q([X || X <- qlc:append(H1, H2)])),
1072             true = R == [1,2,3,4,5,6]">>,
1073
1074          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1075             H2 = qlc:q([X || X <- [4,5,6]]),
1076             R = qlc:e(qlc:q([X || X <- qlc:append(qlc:e(H1), H2)])),
1077             true = R == [1,2,3,4,5,6]">>,
1078
1079          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1080             H2 = [4,5,6],
1081             R = qlc:e(qlc:q([X || X <- qlc:append(H1, H2)])),
1082             true = R == [1,2,3,4,5,6]">>,
1083
1084          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1085             H2 = qlc:q([X || X <- [4,5,6]]),
1086             R = qlc:e(qlc:q([X || X <- qlc:append([H1, H2, H1]), X < 5])),
1087             true = R == [1,2,3,4,1,2,3]">>,
1088
1089          <<"R = qlc:e(qlc:q([X || X <- qlc:append([lista(), anrop()])])),
1090             true = R == [a,b,1,2],
1091             ok.
1092
1093             lista() ->
1094                 [a,b].
1095
1096             anrop() ->
1097                  qlc:q([X || X <- [1,2]]).
1098             foo() -> bar">>,
1099
1100          %% Used to work up to R11B.
1101          %% <<"apa = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3], ugly()])])),
1102          %%   ok.
1103          %%
1104          %%   ugly() ->
1105          %%       [a | apa].
1106          %%   foo() -> bar">>,
1107
1108
1109          %% Maybe this one should fail.
1110          <<"[a|b] = qlc:e(qlc:q([X || X <- qlc:append([[a|b]])])),
1111             ok">>,
1112
1113          <<"17 = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],ugly2()])])),
1114             ok.
1115
1116             ugly2() ->
1117                 [a | fun() -> 17 end].
1118             foo() -> bar">>,
1119
1120          <<"E = ets:new(test, []),
1121             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1122             H = qlc:q([X || X <- qlc:append([ets:table(E), apa])]),
1123             {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1124             false = ets:info(E, safe_fixed),
1125             {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1126             false = ets:info(E, safe_fixed),
1127             {'EXIT',{badarg,_}} = (catch qlc:cursor(H)),
1128             false = ets:info(E, safe_fixed),
1129             F = fun(Obj, A) -> A++[Obj] end,
1130             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], H)),
1131             false = ets:info(E, safe_fixed),
1132             ets:delete(E)">>,
1133
1134          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1135             H2 = qlc:q([X || X <- [a,b,c]]),
1136             R = qlc:e(qlc:q([X || X <- qlc:append(H1,qlc:append(H1,H2))])),
1137             true = R == [1,2,3,1,2,3,a,b,c]">>,
1138
1139          <<"H = qlc:q([X || X <- qlc:append([],qlc:append([[], []]))]),
1140             [] = qlc:e(H)">>,
1141
1142          <<"Q1 = qlc:q([X || X <- [3,4,4]]),
1143             Q2 = qlc:q([X || X <- qlc:sort(qlc:append([[1,2], Q1]))]),
1144             [1,2,3,4,4] = qlc:e(Q2),
1145             [1,2,3,4] = qlc:e(Q2, {unique_all,true})">>,
1146
1147          <<"[] = qlc:e(qlc:q([X || X <- qlc:append([])]))">>,
1148
1149          <<"Q1 = qlc:q([X || X <- [a,b]]),
1150             Q2 = qlc:q([X || X <- [1,2]]),
1151             Q3 = qlc:append([Q1, Q2, qlc:sort([2,1])]),
1152             Q = qlc:q([X || X <- Q3]),
1153             {append, [{list, [a,b]},
1154                       {list, [1,2]},
1155                       {sort,{list, [2,1]},[]}]} = i(Q),
1156             [a,b,1,2,1,2] = qlc:e(Q)">>
1157
1158          ],
1159    run(Config, Ts),
1160    ok.
1161
1162%% Simple call from evaluator.
1163evaluator(Config) when is_list(Config) ->
1164    true = is_alive(),
1165    evaluator_2(Config, []),
1166    {ok, Node} = start_node(qlc_SUITE_evaluator),
1167    ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
1168    test_server:stop_node(Node),
1169    ok.
1170
1171evaluator_2(Config, Apps) ->
1172    lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
1173    FileName = filename:join(?privdir, "eval"),
1174    ok = file:write_file(FileName,
1175                         <<"H = qlc:q([X || X <- L]),
1176                            [1,2,3] = qlc:e(H).">>),
1177    Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
1178    ok = file:eval(FileName, Bs),
1179
1180    %% The error message is "handled" a bit too much...
1181    %% (no trace of erl_lint left)
1182    ok = file:write_file(FileName,
1183             <<"H = qlc:q([X || X <- L]), qlc:e(H).">>),
1184    {error,_} = file:eval(FileName),
1185
1186    %% Ugly error message; badarg is caught by file.erl.
1187    ok = file:write_file(FileName,
1188             <<"H = qlc:q([Z || {X,Y} <- [{a,2}], Z <- [Y]]), qlc:e(H).">>),
1189    {error,_} = file:eval(FileName),
1190
1191    _ = file:delete(FileName),
1192    ok.
1193
1194start_node(Name) ->
1195    PA = filename:dirname(code:which(?MODULE)),
1196    test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
1197
1198%% string_to_handle/1,2.
1199string_to_handle(Config) when is_list(Config) ->
1200    {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
1201    {'EXIT',{badarg,_}} =
1202        (catch qlc:string_to_handle("[X || X <- [a].", unique_all)),
1203    R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
1204    "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
1205    {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
1206    {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
1207    R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
1208        qlc:string_to_handle("bad."),
1209    "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
1210    R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
1211        qlc:string_to_handle("[X || begin Y = [1,2], true end, X <- Y]."),
1212    "1: generated variable 'Y'" ++ _ =
1213        lists:flatten(qlc:format_error(R4)),
1214    {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
1215    H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
1216    [1,2] = qlc:e(H1),
1217    H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
1218                                    "qlc:e(qlc:q([X || X <- [c,d,e]])))]."),
1219    [a,b,c,d,e] = qlc:e(H2),
1220    %% The generated fun has many arguments (erl_eval has a maximum of 20).
1221    H3 = qlc:string_to_handle(
1222           "[{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||"
1223           " {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <- []]."),
1224    [] = qlc:e(H3),
1225    Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
1226    H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
1227    [1,2,3] = qlc:e(H4),
1228    H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
1229    [1,2] = qlc:e(H5),
1230
1231    Ets = ets:new(test, []),
1232    true = ets:insert(Ets, [{1}]),
1233    Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
1234    Q = "[X || {X} <- ets:table(E)].",
1235    [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
1236    [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
1237    [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
1238    {'EXIT',{badarg,_}} =
1239        (catch qlc:string_to_handle(Q, {max_lookup,-1}, Bs2)),
1240    {'EXIT', {no_lookup_to_carry_out, _}} =
1241        (catch qlc:e(qlc:string_to_handle(Q, {lookup,true}, Bs2))),
1242    ets:delete(Ets),
1243
1244    %% References can be scanned and parsed.
1245    E2 = ets:new(test, [bag]),
1246    Ref = make_ref(),
1247    true = ets:insert(E2, [{Ref,Ref}]),
1248    S2 = "[{Val1} || {Ref1, Val1} <- ets:table("++io_lib:write(E2)++"),"
1249         "Ref1 =:= Ref].",
1250    Bs = erl_eval:add_binding('Ref', Ref, erl_eval:new_bindings()),
1251    [{Ref}] = qlc:e(qlc:string_to_handle(S2, [], Bs)),
1252    ets:delete(E2),
1253
1254    ok.
1255
1256%% table
1257table(Config) when is_list(Config) ->
1258    dets:start(),
1259    Ts = [
1260       <<"E = ets:new(test, []),
1261          {'EXIT',{badarg,_}} =
1262               (catch qlc:e(qlc:q([X || X <- ets:table(E, [badarg])]))),
1263          [] = qlc:e(qlc:q([X || X <- ets:table(E)])),
1264          ets:delete(E)">>,
1265
1266       <<"{'EXIT',{badarg,_}} = (catch qlc:table(not_a_fun, []))">>,
1267
1268       <<"E = ets:new(test, []),
1269          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1270          H = qlc:q([{X,Y} || X <- ets:table(E), Y <- ets:table(E)]),
1271          R = qlc:e(H),
1272          ets:delete(E),
1273          [{{1,a},{1,a}},{{1,a},{2,b}},{{1,a},{3,c}},
1274           {{2,b},{1,a}},{{2,b},{2,b}},{{2,b},{3,c}},
1275
1276           {{3,c},{1,a}},{{3,c},{2,b}},{{3,c},{3,c}}] = lists:sort(R)">>,
1277
1278       <<"E = ets:new(test, []),
1279          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1280          H = qlc:q([X || X <- qlc:append([ets:table(E), [a,b,c],
1281                                           ets:table(E)])]),
1282          R = qlc:e(H),
1283          ets:delete(E),
1284          [a,b,c,{1,a},{1,a},{2,b},{2,b},{3,c},{3,c}] = lists:sort(R)">>,
1285
1286       <<"E = ets:new(test, []),
1287          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1288          false = ets:info(E, safe_fixed),
1289          H = qlc:q([{X,Y} || X <- ets:table(E, {n_objects, default}),
1290                              Y <- ets:table(E, {n_objects, 2}),
1291                              false =/= ets:info(E, safe_fixed),
1292                              throw({throw,apa})]),
1293          {throw,apa} = (catch {any_term,qlc:e(H)}),
1294          false = ets:info(E, safe_fixed),
1295          ets:delete(E)">>,
1296
1297       <<"E = ets:new(test, []),
1298          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1299          false = ets:info(E, safe_fixed),
1300          H = qlc:q([{X,Y} || X <- ets:table(E), Y <- ets:table(E),
1301                              false =/= ets:info(E, safe_fixed), exit(apa)]),
1302          {'EXIT',apa} = (catch {any_term,qlc:e(H)}),
1303          false = ets:info(E, safe_fixed),
1304          ets:delete(E)">>,
1305
1306       <<"E = ets:new(test, []),
1307          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1308          H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
1309                              Y <- ets:table(E)]),
1310          R = (catch {any_term,qlc:cursor(H)}),
1311          false = ets:info(E, safe_fixed),
1312          ets:delete(E),
1313          {throw,bad_pre_fun} = R">>,
1314
1315       <<"E = ets:new(test, []),
1316          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1317          H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
1318                              Y <- ets:table(E)]),
1319          R = (catch {any_term,qlc:cursor(H)}),
1320          false = ets:info(E, safe_fixed),
1321          ets:delete(E),
1322          {'EXIT',{bad_pre_fun,_}} = R">>,
1323
1324       <<"E = ets:new(test, [ordered_set]),
1325          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1326          H = qlc:q([X || X <- qlc_SUITE:default_table(E)]),
1327          R = qlc:e(H),
1328          ets:delete(E),
1329          [{1,a},{2,b},{3,c}] = R">>,
1330
1331       <<"E = ets:new(test, [ordered_set]),
1332          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1333          H = qlc:q([X || X <- qlc_SUITE:bad_table(E)]),
1334          {'EXIT', {badarg, _}} = (catch qlc:e(H)),
1335          ets:delete(E)">>,
1336
1337       %% The info tag num_of_objects is currently not used.
1338%%        <<"E = ets:new(test, [ordered_set]),
1339%%           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1340%%           H = qlc:q([X || X <- qlc_SUITE:bad_table_info_fun_n_objects(E)]),
1341%%           {'EXIT', finito} = (catch {any_term,qlc:e(H)}),
1342%%           ets:delete(E)">>,
1343
1344       <<"E = ets:new(test, [ordered_set]),
1345          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1346          H = qlc:q([Y || {X,Y} <- qlc_SUITE:bad_table_info_fun_indices(E),
1347                          X =:= a]),
1348          %% This is due to lookup. If the table were traversed there
1349          %% would be no failure.
1350          {throw, apa} = (catch {any_term,qlc:e(H)}),
1351          ets:delete(E)">>,
1352
1353       <<"E = ets:new(test, [ordered_set]),
1354          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1355          H = qlc:q([Y || {X,Y} <- qlc_SUITE:bad_table_info_fun_keypos(E),
1356                          X =:= a]),
1357          {'EXIT',{keypos,_}} = (catch {any_term,qlc:info(H)}),
1358          {'EXIT',{keypos,_}} = (catch {any_term,qlc:e(H)}),
1359          ets:delete(E)">>,
1360
1361       begin
1362       MS = ets:fun2ms(fun(X) when element(1, X) > 1 -> X end),
1363       [<<"E = ets:new(test, []),
1364           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1365           MS = ">>, io_lib:format("~w", [MS]), <<",
1366           H = qlc:q([{X,Y} || X <- ets:table(E,{traverse,{select, MS}}),
1367                               Y <- ets:table(E)]),
1368           R = qlc:e(H),
1369           ets:delete(E),
1370           [{{2,b},{1,a}},{{2,b},{2,b}},{{2,b},{3,c}},
1371            {{3,c},{1,a}},{{3,c},{2,b}},{{3,c},{3,c}}] = lists:sort(R)">>]
1372       end,
1373
1374       begin % a short table
1375       MS = ets:fun2ms(fun(X) when element(1, X) > 1 -> X end),
1376       [<<"E = ets:new(test, []),
1377           true = ets:insert(E, [{0,b}]),
1378           MS =  ">>, io_lib:format("~w", [MS]), <<",
1379           H1 = qlc:q([X || X <- ets:table(E)]),
1380           R1 = qlc:e(H1),
1381           H2 = qlc:q([X || X <- ets:table(E, {traverse, {select, MS}})]),
1382           R2 = qlc:e(H2),
1383           ets:delete(E),
1384           [_] = R1,
1385           [] = R2">>]
1386       end,
1387
1388       begin
1389       File = filename:join(?privdir, "detsfile"),
1390       _ = file:delete(File),
1391       [<<"{ok, Tab} = dets:open_file(apa, [{file,\"">>, File, <<"\"},
1392                                           {type,bag}]),
1393           ok = dets:insert(Tab, [{1,a},{1,b}]),
1394           R = qlc:e(qlc:q([X || X <- dets:table(Tab)])),
1395           dets:close(Tab),
1396           file:delete(\"">>, File, <<"\"),
1397           R">>]
1398       end,
1399
1400       %% [T || P <- Table, F] turned into a match spec.
1401       <<"E = ets:new(apa, [duplicate_bag]),
1402          true = ets:insert(E, [{1,a},{2,b},{3,c},{4,d}]),
1403          QH = qlc:q([X || {X,_} <- ets:table(E), X > 2], unique),
1404          {qlc, _, [{generate, _, {table, _}}], [{unique,true}]} = i(QH),
1405          [3,4] = lists:sort(qlc:e(QH)),
1406          ets:delete(E)">>,
1407
1408       <<"E = ets:new(apa, []),
1409          true = ets:insert(E, [{1,a},{2,b}]),
1410          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_format(E)),
1411          ets:delete(E)">>,
1412
1413       <<"E = ets:new(apa, []),
1414          true = ets:insert(E, [{1,a},{2,b}]),
1415          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_format_arity(E)),
1416          ets:delete(E)">>,
1417
1418       <<"E = ets:new(apa, []),
1419          true = ets:insert(E, [{1,a},{2,b}]),
1420          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_info_arity(E)),
1421          ets:delete(E)">>,
1422
1423       <<"E = ets:new(apa, []),
1424          true = ets:insert(E, [{1,a},{2,b}]),
1425          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_traverse(E)),
1426          ets:delete(E)">>,
1427
1428       <<"E = ets:new(apa, []),
1429          true = ets:insert(E, [{1,a},{2,b}]),
1430          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_post(E)),
1431          ets:delete(E)">>,
1432
1433       <<"E = ets:new(apa, []),
1434          true = ets:insert(E, [{1,a},{2,b}]),
1435          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_max_lookup(E)),
1436          ets:delete(E)">>,
1437
1438       <<"E = ets:new(apa, []),
1439          true = ets:insert(E, [{1,a},{2,b}]),
1440          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_lookup(E)),
1441          ets:delete(E)">>,
1442
1443       <<"L = [{1,a},{2,b},{3,c}],
1444          QH = qlc:q([element(2, X) || X <- qlc_SUITE:table(L, [2]),
1445                                       (element(1, X) =:= 1)
1446                                        or (2 =:= element(1, X))]),
1447          [a,b] = lists:sort(qlc:e(QH))">>,
1448
1449       <<"etsc(fun(E) ->
1450              Q = qlc:q([{A,B} || {A,B} <-
1451                                qlc:q([{B,A} || {A,B} <- ets:table(E),
1452                                                (A =:= 1) or (A =:= 2),
1453                                                math:sqrt(B) < A])]),
1454              [{2,2}] = qlc:eval(Q),
1455              [1,2] = lookup_keys(Q)
1456           end, [{1,1},{2,2}])">>
1457       ],
1458    run(Config, Ts),
1459
1460    Ts2 = [
1461       %% [T || P <- Table, F] turned into a match spec. Records needed.
1462       <<"E = ets:new(foo, [bag]),
1463          ets:insert(E, [{a,1,2},#a{b=3,c=4},{a,3}]),
1464          QH = qlc:q([X || X <- ets:table(E), is_record(X, a)]),
1465          {list,{table,_}, _} = i(QH),
1466          [{a,1,2},{a,3,4}] = lists:sort(qlc:eval(QH)),
1467          ets:delete(E)">>
1468       ],
1469    run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
1470
1471    ok.
1472
1473%% Caller or cursor process dies.
1474process_dies(Config) when is_list(Config) ->
1475    Ts = [
1476       <<"E = ets:new(test, []),
1477          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1478          false = ets:info(E, safe_fixed),
1479          Parent = self(),
1480          F = fun() ->
1481                      H = qlc:q([X || X <- ets:table(E)]),
1482                      qlc:cursor(H),
1483                      Parent ! {self(),ok}
1484              end,
1485          Pid = spawn_link(F),
1486          receive {Pid,ok} -> ok end,
1487          timer:sleep(10),
1488          false = ets:info(E, safe_fixed),
1489          ets:delete(E)">>,
1490
1491       <<"%% This is not nice. The cursor's monitor kicks in.
1492          E = ets:new(test, []),
1493          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1494          false = ets:info(E, safe_fixed),
1495          Parent = self(),
1496          F = fun() ->
1497                      H = qlc:q([X || begin
1498                                          process_flag(trap_exit, false),
1499                                          {links, [Pid]} =
1500                                              process_info(self(), links),
1501                                          unlink(Pid),
1502                                          timer:sleep(1),
1503                                          {links, []} =
1504                                              process_info(self(), links),
1505                                          true
1506                                      end,
1507                                      X <- ets:table(E)]),
1508                      C = qlc:cursor(H),
1509                      qlc:next_answers(C),
1510                      Parent ! {self(),ok}
1511              end,
1512          Pid = spawn_link(F),
1513          receive {Pid,ok} -> ok end,
1514          timer:sleep(10),
1515          false = ets:info(E, safe_fixed),
1516          ets:delete(E)">>,
1517
1518       <<"H = qlc:q([X || X <- [1,2]]),
1519          {qlc_cursor, Term} = C = qlc:cursor(H),
1520          PF = process_flag(trap_exit, true),
1521          F = fun(T) -> not is_pid(T) end,
1522          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1523          exit(Pid, kill),
1524          timer:sleep(1),
1525          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1526                (catch qlc:next_answers(C)),
1527          process_flag(trap_exit, PF)">>,
1528       <<"H = qlc:q([X || begin process_flag(trap_exit, true), true end,
1529                          X <- [1,2]]),
1530          {qlc_cursor, Term} = C = qlc:cursor(H),
1531          PF = process_flag(trap_exit, true),
1532          F = fun(T) -> not is_pid(T) end,
1533          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1534          [1] = qlc:next_answers(C, 1),
1535          exit(Pid, stop),
1536          timer:sleep(1),
1537          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1538              (catch qlc:next_answers(C)),
1539          process_flag(trap_exit, PF)">>,
1540       <<"%% This is not nice. No cleanup is done...
1541          H = qlc:q([X || begin process_flag(trap_exit, false), true end,
1542                     X <- [1,2]]),
1543          {qlc_cursor, Term} = C = qlc:cursor(H),
1544          PF = process_flag(trap_exit, true),
1545          F = fun(T) -> not is_pid(T) end,
1546          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1547          [1] = qlc:next_answers(C, 1),
1548          exit(Pid, stop),
1549          timer:sleep(1),
1550          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1551              (catch qlc:next_answers(C)),
1552          process_flag(trap_exit, PF)">>,
1553
1554       <<"PF = process_flag(trap_exit, true),
1555          E = ets:new(test, []),
1556          %% Hard kill. No cleanup will be done.
1557          H = qlc:q([X || begin exit(self(), kill), true end,
1558                          X <- ets:table(E)]),
1559          C = qlc:cursor(H),
1560          {'EXIT', {{qlc_cursor_pid_no_longer_exists, _}, _}} =
1561               (catch qlc:next_answers(C)),
1562          false = ets:info(E, safe_fixed), % - but Ets cleans up anyway.
1563          true = ets:delete(E),
1564          process_flag(trap_exit, PF)">>,
1565
1566       <<"E = ets:new(test, []),
1567          true = ets:insert(E, [{1,a}]),
1568          %% The signal is caught by trap_exit. No process dies...
1569          H = qlc:q([X || begin exit(self(), normal), true end,
1570                          X <- ets:table(E)]),
1571          C = qlc:cursor(H, {spawn_options, []}),
1572          [{1,a}] = qlc:next_answers(C),
1573          qlc:delete_cursor(C),
1574          false = ets:info(E, safe_fixed),
1575          true = ets:delete(E)">>,
1576       <<"E = ets:new(test, []),
1577          true = ets:insert(E, [{1,a}]),
1578          %% The same as last example.
1579          H = qlc:q([X || begin
1580                              process_flag(trap_exit, true),
1581                              exit(self(), normal), true
1582                          end,
1583                          X <- ets:table(E)]),
1584          C = qlc:cursor(H, {spawn_options, []}),
1585          [{1,a}] = qlc:next_answers(C),
1586          qlc:delete_cursor(C),
1587          false = ets:info(E, safe_fixed),
1588          true = ets:delete(E), ok">>,
1589       <<"E = ets:new(test, []),
1590          true = ets:insert(E, [{1,a}]),
1591          H = qlc:q([X || X <- ets:table(E)]),
1592          SpawnOpts = [link, monitor], % monitor is ignored
1593          {qlc_cursor, Term} = C = qlc:cursor(H, {spawn_options, SpawnOpts}),
1594          F = fun(T) -> not is_pid(T) end,
1595          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1596          Me = self(),
1597          qlc_SUITE:install_error_logger(),
1598          Tuple = {this, tuple, is, writton, onto, the, error_logger},
1599          SP = spawn(fun() ->
1600                  Pid ! Tuple,
1601                  Me ! {self(), done}
1602                end),
1603          receive {SP, done} -> ok end,
1604          [{1,a}] = qlc:next_answers(C),
1605          qlc:delete_cursor(C),
1606          {error, _Pid, Tuple} = qlc_SUITE:read_error_logger(),
1607          qlc_SUITE:uninstall_error_logger(),
1608          false = ets:info(E, safe_fixed),
1609          true = ets:delete(E), ok">>
1610
1611        ],
1612    run(Config, Ts),
1613    ok.
1614
1615%% The sort option.
1616sort(Config) when is_list(Config) ->
1617    Ts = [
1618       <<"H = qlc:q([X || X <- qlc:sort([1,2,3,2], {unique,true})]),
1619          [1,2,3] = qlc:e(H),
1620          C1 = qlc:cursor(H),
1621          [1,2,3] = qlc:next_answers(C1, all_remaining),
1622          qlc:delete_cursor(C1)">>,
1623
1624       <<"H = qlc:q([{X,Y} || X <- qlc:sort(qlc:q([X || X <- [1,2,3,2]]),
1625                                            {unique,true}),
1626                              Y <- [a,b]]),
1627          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H),
1628          C = qlc:cursor(H),
1629          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1630              qlc:next_answers(C, all_remaining),
1631          qlc:delete_cursor(C)">>,
1632
1633       <<"H = qlc:q([X || X <- qlc:sort(qlc:q([X || X <- apa]))]),
1634          {'EXIT',{badarg,_}} = (catch qlc:e(H))">>,
1635
1636          %% An example with a side effect. The result may vary...
1637       <<"E = ets:new(test, [duplicate_bag]),
1638          true = ets:insert(E, [{1,17},{1,a}]),
1639          H_1 = qlc:q([X || X <- ets:table(E)]),
1640          H = qlc:q([X || X <- [1,2,3], ets:insert(E, {1,-X}),
1641                          {_,Y} <- H_1,
1642                          X > Y]),
1643          true = lists:sort(qlc:e(H)) == [1,2,2,3,3,3],
1644          true = ets:delete(E)">>,
1645
1646       <<"E = ets:new(test, [duplicate_bag]),
1647          true = ets:insert(E, [{1,17}]),
1648          H_1 = qlc:q([X || X <- qlc:sort(ets:tab2list(E))]),
1649          %% Note: side effect in filter!
1650          H = qlc:q([X || X <- [1,2,3], ets:insert(E, {1,-X}),
1651                          {_,Y} <- H_1, X > Y]),
1652          [] = qlc:e(H),
1653          true = ets:delete(E)">>,
1654
1655       <<"H = qlc:q([X || X <- qlc:sort([1,2,3], {fopp,la})]),
1656          {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1657          {'EXIT',{badarg,_}} = (catch qlc:cursor(H)),
1658          F = fun(Obj, A) -> A++[Obj] end,
1659          {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], H))">>,
1660
1661       <<"Q1 = qlc:q([X || X <- [1,2]]),
1662          AL = [Q1, [1,2,3]],
1663          Q2 = qlc:q([X || X <- qlc:sort(qlc:append(AL))]),
1664          [1,1,2,2,3] = qlc:e(Q2)">>,
1665
1666       <<"H = qlc:q([{X,Y} || X <- qlc:sort(qlc:q([X || X <- [1,2,3,2]]),
1667                                            {unique,true}),
1668                              Y <- [a,b]]),
1669          {qlc, _,
1670           [{generate, _, {sort, {qlc, _, [{generate, _, {list, [1,2,3,2]}}],
1671                                  [{unique,true}]},
1672                           []}},
1673            {generate, _, {qlc, _, [{generate, _, {list, [a,b]}}],
1674                           [{unique,true}]}}],
1675           [{unique,true}]} = i(H, unique_all),
1676          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H, unique_all)">>,
1677
1678       <<"L = [1,2,1,3,4,3,1],
1679          true = lists:sort(L) == qlc:e(qlc:q([X || X <- qlc:sort(L)])),
1680          true = lists:usort(L) ==
1681                 qlc:e(qlc:q([X || X <- qlc:sort(L, {unique,true})])),
1682          true = lists:reverse(lists:sort(L)) ==
1683                 qlc:e(qlc:q([X || X <- qlc:sort(L, {order, descending})])),
1684          true = lists:reverse(lists:usort(L)) ==
1685                 qlc:e(qlc:q([X || X <- qlc:sort(L, [{order, descending},
1686                                                     {unique, true}])])),
1687          CF = fun(X, Y) -> X =< Y end,
1688          true = lists:sort(L) ==
1689                 qlc:e(qlc:q([X || X <- qlc:sort(L, {order, CF})])),
1690          true = lists:usort(L) ==
1691                 qlc:e(qlc:q([X || X <- qlc:sort(L, [{order, CF},
1692                                                    {unique, true}])]))">>,
1693
1694       <<"E = ets:new(foo, []),
1695          [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
1696          H = qlc:q([{X,Y} || X <- [a,b], Y <- qlc:sort(ets:table(E))]),
1697          100000 = length(qlc:e(H)),
1698          ets:delete(E)">>
1699
1700        ],
1701    run(Config, Ts),
1702    ok.
1703
1704%% The sort option.
1705keysort(Config) when is_list(Config) ->
1706
1707    Ts = [
1708       <<"OF = fun(X, Y) -> X =< Y end,
1709          F = fun(Obj, A) -> A++[Obj] end,
1710          H = qlc:q([X || X <- qlc:keysort(1, [{2,a},{1,b}], {order,OF})]),
1711          {'EXIT',{{badarg,order},_}} = (catch qlc:e(H)),
1712          {'EXIT',{{badarg,order},_}} = (catch qlc:fold(F, [], H)),
1713          {'EXIT',{{badarg,order},_}} = (catch qlc:cursor(H))">>,
1714
1715       <<"E = create_ets(1, 2),
1716          H = qlc:q([X || X <- qlc:keysort([1], ets:table(E),
1717                                           [{size,1},{tmpdir,\"/a/b/c\"}])]),
1718          H1 = qlc:q([X || {X,_} <- qlc:e(H), X < 4]),
1719          {error,_,{file_error,_,_}} = qlc:info(H1),
1720          {error,_,{file_error,_,_}} = qlc:e(H1),
1721          ets:delete(E)">>,
1722
1723       <<"L = [{1,a},{2,b},{3,c},{2,b}],
1724          H = qlc:q([{X,Y} || {X,_} <- qlc:keysort(1, qlc:q([X || X <- L]),
1725                                                   {unique,true}),
1726                              Y <- [a,b]]),
1727          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H),
1728          C = qlc:cursor(H),
1729          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1730              qlc:next_answers(C, all_remaining),
1731          qlc:delete_cursor(C)">>,
1732
1733       <<"H1 = qlc:q([X || X <- qlc:keysort(0, [])]),
1734          {'EXIT',{badarg,_}} = (catch qlc:e(H1)),
1735          H2 = qlc:q([X || X <- qlc:keysort(1, [], {bad,arg})]),
1736          {'EXIT',{badarg,_}} = (catch qlc:e(H2)),
1737          H3 = qlc:q([X || X <- qlc:keysort([], [])]),
1738          {'EXIT',{badarg,_}} = (catch qlc:e(H3))">>,
1739
1740       <<"H = qlc:q([X || X <- qlc:keysort(1, [{1,a},{2,b}],
1741                                           [{order,descending},
1742                                           {compressed,true}])]),
1743          [{2,b},{1,a}] = qlc:e(H),
1744          H2 = qlc:q([X || X <- qlc:keysort(1, [{1},{2}], compressed)]),
1745          {'EXIT', {badarg, _}} = (catch qlc:e(H2))">>,
1746
1747       <<"H = qlc:q([X || X <- qlc:keysort(1, [{1,a},{2,b}], {compressed,false})]),
1748          [{1,a},{2,b}] = qlc:e(H)">>,
1749
1750       <<"E = create_ets(1, 2),
1751          H = qlc:q([X || X <- qlc:keysort([1], ets:table(E),
1752                                           [{size,1},{tmpdir,\"/a/b/c\"}])]),
1753          F = fun(Obj, A) -> A++[Obj] end,
1754          {error,_,{file_error,_,_}} = qlc:e(H),
1755          \" \\\"no such\" ++ _ = lists:dropwhile(fun(A) -> A =/= $\s end,
1756                                 lists:flatten(qlc:format_error(qlc:e(H)))),
1757          {error,_,{file_error,_,_}} = qlc:e(H, {unique_all,true}),
1758          {error,_,{file_error,_,_}} = qlc:cursor(H),
1759          {error,_,{file_error,_,_}} = qlc:cursor(H, {unique_all,true}),
1760          {error,_,{file_error,_,_}} = qlc:cursor(H, {spawn_options, []}),
1761          {error,_,{file_error,_,_}} = qlc:cursor(H, {spawn_options,default}),
1762          {error,_,{file_error,_,_}} =
1763               qlc:cursor(H, [{unique_all,true},{spawn_options, []}]),
1764          {error,_,{file_error,_,_}} = qlc:fold(F, [], H),
1765          {error,_,{file_error,_,_}} = qlc:fold(F, [],H, {unique_all,true}),
1766          ets:delete(E)">>,
1767
1768       <<"L = [{1,b,a},{1,b,b},{1,a,a}],
1769          H = qlc:q([X || X <- qlc:keysort([4,1], L)]),
1770          {error,_,bad_object} = qlc:e(H),
1771          \"the keys\" ++ _ = qlc:format_error(qlc:e(H))">>,
1772
1773       begin
1774       File = filename:join(?privdir, "afile"),
1775       ok = file:write_file(File, <<>>),
1776       [<<"H = qlc:q([X || X <- qlc:keysort([1], [{1},{2},{1}],
1777                                            [{tmpdir,\"">>, File, <<"\"},
1778                                             {size,1}])]),
1779           {error,_,{file_error,_,_}} = qlc:e(H),
1780           file:delete(\"">>, File, <<"\")">>]
1781       end,
1782
1783       <<"H0 = qlc:q([X || X <- [1,2,3]]),
1784          H = qlc:q([X || X <- qlc:sort(H0,{tmpdir,\".\"})]),
1785          [1,2,3] = qlc:e(H)">>,
1786
1787       %% The global option 'tmpdir' takes precedence.
1788       begin
1789       PrivDir = ?privdir,
1790       [<<"L = [{1,a},{2,b}],
1791           H = qlc:q([X || X <- qlc:keysort([1], L, {tmpdir,\"/a/b/c\"})]),
1792           H1 = qlc:q([X || X <- H, X > 3]),
1793           Dir = \"">>, PrivDir, <<"\",
1794           Options = [{tmpdir, Dir}],
1795           {qlc,_,[{generate,_,{keysort,{list,L},[1],[{tmpdir,Dir}]}},_],[]} =
1796                i(H1, Options),
1797           [{1,a},{2,b}] = qlc:e(H1, Options)">>] % no check of "/a/b/c"
1798       end,
1799
1800       <<"L = [{2,c},{1,b},{1,a},{3,a},{1,c},{2,b}],
1801          true = lists:sort(L) ==
1802                 qlc:e(qlc:q([X || X <- qlc:keysort([1,2], L)]))">>,
1803
1804       <<"L = [{1,b},{2,c},{1,a},{3,e},{4,f},{3,d}],
1805          true = lists:keysort(1, L) ==
1806                 qlc:e(qlc:q([X || X <- qlc:keysort(1,L)])),
1807          true = lists:ukeysort(1, L) ==
1808                 qlc:e(qlc:q([X || X <- qlc:keysort(1, L, {unique,true})])),
1809          true = lists:reverse(lists:keysort(1, L)) ==
1810                 qlc:e(qlc:q([X || X <- qlc:keysort(1,L,
1811                                                    {order, descending})])),
1812          true = lists:reverse(lists:ukeysort(1, L)) ==
1813                 qlc:e(qlc:q([X || X <- qlc:keysort(1, L, [{unique,true},
1814                                                {order, descending}])]))">>,
1815
1816       <<"L = [{X} || X <- lists:seq(1,100000)],
1817          H1 = qlc:append([L,[{1,2},{2,3},{3,4}]]),
1818          H = qlc:keysort([1], qlc:keysort([1], H1, [{compressed,true}])),
1819          R = qlc:e(H),
1820          100003 = length(R)">>
1821
1822        ],
1823    run(Config, Ts),
1824
1825    ok.
1826
1827%% keysort/1,2, using a file.
1828filesort(Config) when is_list(Config) ->
1829    Ts = [
1830       <<"Q = qlc:q([X || X <- [{3},{1},{2}]]),
1831          Opts = [{size,10},{no_files,3}],
1832          Q2 = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:keysort([1],Q,Opts)]),
1833          [{{1},1},{{2},1},{{3},1},{{1},2},{{2},2},{{3},2}] = qlc:e(Q2)">>
1834        ],
1835    run(Config, Ts),
1836    ok.
1837
1838
1839%% The cache option.
1840cache(Config) when is_list(Config) ->
1841    Ts = [
1842       <<"{'EXIT', {badarg, _}} = (catch qlc:q([X || X <- [1,2]], badarg))">>,
1843
1844       <<"Q1 = qlc:q([X || X <- [1,2,1,2,1]], {unique,true}),
1845          [1,2] = qlc:e(Q1),
1846          [1,2] = qlc:e(Q1, {unique_all,true}),
1847          Q2 = qlc:q([X || X <- qlc:q([X || X <- [1,2,1,2,1]],
1848                                      {unique,true})]),
1849          [1,2] = qlc:e(Q2),
1850          [1,2] = qlc:e(Q2, {unique_all,true}),
1851          Q3 = qlc:q([X || X <- qlc:append([[1,2,3], [4,5,6]])]),
1852          [1,2,3,4,5,6] = qlc:e(Q3)">>,
1853
1854       <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{2,a},{1,b},{2,b}]]),
1855          Q2 = qlc:q([{X,make_ref()} || X <- Q1]),
1856          [{1,_},{2,_},{1,_},{2,_}] = qlc:e(Q2, {unique_all,false}),
1857          [{1,_},{2,_}] = qlc:e(Q2, {unique_all,true})">>,
1858
1859       <<"E = ets:new(test, [duplicate_bag]),
1860          true = ets:insert(E, [{1,a},{2,a},{1,b},{2,b}]),
1861          Q1 = qlc:q([X || {X,_} <- ets:table(E)]),
1862          Q2 = qlc:q([{X,make_ref()} || X <- Q1]),
1863          [{1,_},{1,_},{2,_},{2,_}] = lists:sort(qlc:e(Q2, {unique_all,false})),
1864          [{1,_},{2,_}] = lists:sort(qlc:e(Q2, {unique_all,true})),
1865          ets:delete(E)">>,
1866
1867       <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{2,a},{1,b},{2,b}]]),
1868          Q2 = qlc:q([{X,make_ref()} || X <- qlc:append([Q1, Q1])]),
1869          [{1,_},{2,_},{1,_},{2,_},{1,_},{2,_},{1,_},{2,_}] =
1870                qlc:e(Q2, {unique_all,false}),
1871          [{1,_},{2,_}] = qlc:e(Q2, {unique_all,true})">>,
1872
1873       <<"[] = qlc:e(qlc:q([X || X <- []], {unique, true})),
1874          [] = qlc:e(qlc:q([X || X <- qlc:q([X || X <- qlc:append([])],
1875                                             {unique,true})]))">>,
1876
1877       <<"Q1 = qlc:q([{X,make_ref()} || {X,_} <- [{1,a},{1,b}]]),
1878          [{1,_},{1,_}] = qlc:e(Q1, {unique_all, true}),
1879          Q2 = qlc:q([Y || {X,_} <- [{1,a},{1,b}],
1880                           begin Y = {X,make_ref()}, true end]),
1881          [{1,_},{1,_}] = qlc:e(Q2, {unique_all,true}),
1882          Q3 = qlc:q([Y || X <- [{1,a},{2,a}],
1883                           begin {_,Z} = X, Y = {Z,make_ref()}, true end]),
1884          [{a,_},{a,_}] = qlc:e(Q3, {unique_all, true})">>,
1885
1886       <<"E = ets:new(apa, [duplicate_bag]),
1887          ets:insert(E, [{1,a},{2,a},{1,a}]),
1888          H1 = qlc:q([X || X <- qlc:append(ets:table(E),[7,3,5])],
1889                          {cache, true}),
1890          [{_,a},{_,a},{_,a},7,3,5] = qlc:e(H1),
1891          ets:delete(E)">>,
1892
1893       <<"F = fun(Obj, A) -> A++[Obj] end,
1894          H = qlc:q([X || X <- [1,3,2,4]], cache),
1895          Q = qlc:q([X || X <- H]),
1896          [1,3,2,4] = qlc:fold(F, [], Q, [])">>,
1897
1898       <<"F = fun(Obj, A) -> A++[Obj] end,
1899          E = ets:new(apa, [duplicate_bag]),
1900          true = ets:insert(E, [{1,a},{2,b},{1,a}]),
1901          Q1 = qlc:q([X || X <- ets:table(E)], [cache, unique]),
1902          Q = qlc:q([X || X <- Q1], [cache, unique]),
1903          {qlc, _, [{generate, _,{table,_}}], [{unique,true}]} = i(Q),
1904          R = qlc:fold(F, [], Q, []),
1905          ets:delete(E),
1906          true = [{1,a},{2,b}] == lists:sort(R)">>,
1907
1908       <<"E = ets:new(apa, [duplicate_bag]),
1909          ets:insert(E, [{1,a},{2,b},{1,a}]),
1910          H1 = qlc:q([X || X <- qlc:append(ets:table(E),[7,3])], cache),
1911          H2 = qlc:q([{Y,X} || Y <- [2,1,3], X <- H1]),
1912          [{2,_},{2,_},{2,_},{2,7},{2,3},
1913           {1,_},{1,_},{1,_},{1,7},{1,3},
1914           {3,_},{3,_},{3,_},{3,7},{3,3}] = qlc:e(H2),
1915          ets:delete(E)">>,
1916
1917          %% This case is not 100 percent determined. An Ets table
1918          %% is updated in a filter and later used in a generator.
1919       <<"E = ets:new(apa, [bag]),
1920          true = ets:insert(E, [{1,a},{2,b}]),
1921          H1 = qlc:q([Y || Y <- ets:table(E)],
1922                     [{cache, no}, {unique, true}]),
1923          H = qlc:q([{X,Y} || X <- [{1,a},{2,d},{3,e}],
1924                              ets:insert(E, X),
1925                              Y <- H1]),
1926          [{{1,a},_}, {{1,a},_}, {{2,d},_}, {{2,d},_}, {{2,d},_},
1927           {{3,e},_}, {{3,e},_}, {{3,e},_}, {{3,e},_}] = qlc:e(H),
1928          ets:delete(E)">>,
1929
1930          %% This case is not 100 percent determined. An Ets table
1931          %% is updated in a filter and later used in a generator.
1932       <<"E = ets:new(apa, [bag]),
1933          true = ets:insert(E, [{1,a},{2,b}]),
1934          H1 = qlc:q([Y || Y <- ets:table(E)],
1935                     [{cache, true}, {unique, true}]),
1936          H = qlc:q([{X,Y} || X <- [{1,a},{2,d},{3,e}],
1937                              ets:insert(E, X),
1938                              Y <- H1]),
1939          [{{1,a},_}, {{1,a},_}, {{2,d},_}, {{2,d},_}, {{3,e},_}, {{3,e},_}] =
1940              qlc:e(H),
1941          ets:delete(E)">>,
1942
1943       <<"%% {5979} and {5549} are both hashed to 28244 by phash2/1
1944          E = ets:new(apa, [duplicate_bag]),
1945          true = ets:insert(E, [{5979},{5549},{5979},{5549},{0}]),
1946          H1 = qlc:q([X || X <- ets:table(E)],
1947                     [{cache, true}, {unique, true}]),
1948          H = qlc:q([Y || _ <- [1,2], Y <- H1]),
1949          {qlc, _, [{generate, _, {list, [1,2]}},
1950                    {generate, _, {qlc, _, [{generate, _, {table,_}}],
1951                                   [{cache,ets},{unique,true}]}}],
1952           []} = i(H),
1953          [{0},{0},{5549},{5549},{5979},{5979}] = lists:sort(qlc:e(H)),
1954          ets:delete(E)">>,
1955
1956       <<"E = ets:new(apa, [ordered_set]),
1957          ets:insert(E, [{1},{2}]),
1958          H1 = qlc:q([X || X <- ets:table(E)], [cache, unique]),
1959          H2 = qlc:q([X || Y <- [3,4], ets:insert(E, {Y}), X <- H1]),
1960          {qlc, _, [{generate, _, {list, [3,4]}}, _,
1961                    {generate, _, {qlc, _, [{generate, _,
1962                                             {table, _}}],
1963                                   [{cache, ets}]}}],
1964           []} = i(H2),
1965          [{1},{2},{3},{1},{2},{3}] = qlc:e(H2),
1966          ets:delete(E)">>,
1967
1968       <<"E = ets:new(apa, [ordered_set]),
1969          ets:insert(E, [{1},{2}]),
1970          H1 = qlc:q([X || X <- ets:table(E)], [unique]),
1971          H2 = qlc:q([X || Y <- [3,4], ets:insert(E, {Y}), X <- H1]),
1972          [{1},{2},{3},{1},{2},{3},{4}] = qlc:e(H2),
1973          ets:delete(E)">>,
1974
1975       <<"H0 = qlc:append([a,b], [c,d]),
1976          H = qlc:q([{X,Y} ||
1977                        X <- H0,
1978                        Y <- qlc:q([{X1,Y} ||
1979                                       X1 <- H0,
1980                                       Y <- qlc:q([{X2,Y} ||
1981                                                      X2 <- H0,
1982                                                      Y <- H0])])]),
1983          {qlc, _,
1984           [{generate, _,{append, [{list, [a,b]}, {list, [c,d]}]}},
1985            {generate, _,
1986             {qlc, _,
1987              [{generate, _, {append,[{list, [a,b]},{list, [c,d]}]}},
1988               {generate, _,
1989                {qlc, _,
1990                 [{generate, _,{append,[{list, [a,b]}, {list, [c,d]}]}},
1991                  {generate, _,{append,[{list, [a,b]}, {list, [c,d]}]}}],
1992                 [{cache,ets}]}}],
1993              [{cache,ets}]}}],
1994           []} = i(H, cache_all)">>
1995
1996       ],
1997    run(Config, Ts),
1998    ok.
1999
2000%% OTP-6038. The {cache,list} option.
2001cache_list(Config) when is_list(Config) ->
2002    Ts = [
2003       begin
2004       PrivDir = ?privdir,
2005       [<<"%% unique, cache list. A simple qlc.
2006          Options = [{cache,list}, unique],
2007          L0 = [1,2,3,4,1,2,3,4],
2008          L = qlc_SUITE:table(L0, []),
2009          Q1 = qlc:q([X || X <- L], Options),
2010          Q = qlc:q([{X,Y} || X <- [a,b], Y <- Q1]),
2011          GOptions = [{tmpdir,\"">>, PrivDir, <<"\"}],
2012          {qlc,_,[{generate,_,{list,[a,b]}},
2013                  {generate,_,{qlc,_,
2014                               [{generate,_,{table,_}}],
2015                               [{cache,list},{unique,true}]}}],
2016           []} = i(Q, GOptions),
2017          true = [{X,Y} || X <- [a,b], Y <- [1,2,3,4]] =:=
2018                 qlc:e(Q, GOptions)">>]
2019       end,
2020
2021       begin
2022       MS = ets:fun2ms(fun({X,_}) when X > 1 -> X end),
2023       [<<"%% No cache, even if explicit match specification.
2024          etsc(fun(E) ->
2025                   MS =  ">>, io_lib:format("~w", [MS]), <<",
2026                   Options = [{cache,list}, unique],
2027                   Q = qlc:q([{X,Y} ||
2028                                 X <- ets:table(E, {traverse, {select, MS}}),
2029                                 Y <- [1,2,3]],
2030                             Options),
2031                   {qlc,_,[{generate,_,{table,{ets,table,_}}},
2032                           {generate,_,{list,[1,2,3]}}],
2033                    [{unique,true}]} = i(Q),
2034                   true = [{X,Y} || X <- lists:seq(2,10), Y <- [1,2,3]] =:=
2035                       lists:sort(qlc:e(Q))
2036               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>]
2037       end,
2038
2039       <<"%% Temporary files.
2040          %% Remove list expression caches when possible. (no visible effect)
2041          T = lists:seq(1, 100000), % Huge terms on file
2042          F = fun(C) ->
2043                      Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
2044                                 {cache,C}),
2045                      Q1 = qlc:q([{X,Y,Z} ||
2046                                     X <- Q0,
2047                                     Y <- Q0,
2048                                     Z <- Q0],
2049                                 {cache,C}),
2050                      qlc:q([{X, Y} || Y <- [1], X <- Q1])
2051              end,
2052          Ql = F(list),
2053          Rl = qlc:e(Ql, {max_list_size, 64*1024}),
2054          Qe = F(ets),
2055          Re = qlc:e(Qe),
2056          Qf = F(no),
2057          Rf = qlc:e(Qf),
2058          Ri = qlc:e(Ql, {max_list_size, 1 bsl 35}), % heavy
2059          {27,27,27,27,true,true,true} =
2060              {length(Rl), length(Re), length(Rf), length(Ri),
2061               Rl =:= Re, Re =:= Rf, Rf =:= Ri}">>,
2062
2063       <<"%% File sorter.
2064          T = lists:seq(1, 10000),
2065          F = fun(C) ->
2066                      Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
2067                                 [{cache,C},unique]),
2068                      Q1 = qlc:q([{X,Y,Z} ||
2069                                     X <- Q0,
2070                                     Y <- Q0,
2071                                     Z <- Q0],
2072                                 [{cache,C},unique]),
2073                      qlc:q([{X, Y} || Y <- [1], X <- Q1])
2074              end,
2075          GOpt = [{max_list_size, 10000}],
2076          Ql = F(list),
2077          Rl = qlc:e(Ql, GOpt),
2078          Qe = F(ets),
2079          Re = qlc:e(Qe, GOpt),
2080          Qf = F(no),
2081          Rf = qlc:e(Qf, GOpt),
2082          {1,1,1,true,true} =
2083              {length(Rl), length(Re), length(Rf), Rl =:= Re, Re =:= Rf}">>,
2084
2085       <<"%% Remove list expression caches when possible. (no visible effect)
2086          Q0 = qlc:q([{X} || X <- [1,2,3], begin X > 0 end], {cache,list}),
2087          Q1 = qlc:q([{X,Y,Z} ||
2088                         X <- Q0,
2089                         Y <- Q0,
2090                         Z <- Q0],
2091                     {cache,list}),
2092          Q = qlc:q([{X, Y} || Y <- [1], X <- Q1]),
2093          R = qlc:e(Q),
2094          L0 = [{X} || X <- [1,2,3], begin X > 0 end],
2095          L1 = [{X,Y,Z} ||
2096                   X <- L0,
2097                   Y <- L0,
2098                   Z <- L0],
2099          L = [{X, Y} || Y <- [1], X <- L1],
2100          true = R =:= L">>,
2101
2102       <<"%% No temporary file.
2103          L = [{I,a} || I <- lists:seq(1, 10)],
2104          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2105                           begin element(1, X) > 5 end],
2106                     {cache,list}),
2107          Q = qlc:q([{X, element(1,Y)} ||
2108                        X <- lists:seq(1, 5),
2109                        Y <- Q0]),
2110          err = qlc:e(Q)">>,
2111
2112       <<"%% Sort internally.
2113          L = [{I,a} || I <- lists:seq(1, 10)],
2114          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2115                           begin element(1, X) > 5 end],
2116                     [unique,{cache,list}]),
2117          Q = qlc:q([{X, element(1,Y)} ||
2118                        X <- lists:seq(1, 5),
2119                        Y <- Q0]),
2120          err = qlc:e(Q, {max_list_size,0})">>,
2121
2122       <<"%% No temporary file.
2123          etsc(fun(E) ->
2124                       Q0 = qlc:q([X || X <- ets:table(E),
2125                                        begin element(1, X) > 5 end],
2126                                  {cache,list}),
2127                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2128                                                       Y <- Q0]),
2129                       R = [{X,Y} || X <- lists:seq(1, 5),
2130                                     Y <- lists:seq(6, 10)],
2131                       R = lists:sort(qlc:e(Q))
2132               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>,
2133
2134       <<"%% Sort internally
2135          etsc(fun(E) ->
2136                       Q0 = qlc:q([X || X <- ets:table(E),
2137                                        begin element(1, X) > 5 end],
2138                                  [{cache,list},unique]),
2139                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2140                                                       Y <- Q0]),
2141                       R = [{X,Y} || X <- lists:seq(1, 5),
2142                                     Y <- lists:seq(6, 10)],
2143                       R = lists:sort(qlc:e(Q))
2144               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>,
2145
2146       <<"%% A few more tests of unique and {cache,list}.
2147          F = fun(CU) ->
2148                      H1 = qlc:q([{X,Y} ||
2149                                     Y <- [a,b],
2150                                     X <- [1,2]],
2151                                 CU),
2152                      qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1])
2153              end,
2154          Q1 = F([]),
2155          Q2 = F([{cache,list}, unique]),
2156          R1 = qlc:e(Q1),
2157          R2 = qlc:e(Q2),
2158          R3 = qlc:e(Q2, {max_list_size, 0}), % still in RAM
2159          true = R1 =:= R2,
2160          true = R2 =:= R3">>,
2161
2162       <<"E = ets:new(t, [duplicate_bag]),
2163          true = ets:insert(E, [{2},{1},{2}]),
2164          H1 = qlc:q([{X,Y} ||
2165                         Y <- [a,b],
2166                         {X} <- ets:table(E)],
2167                     [{cache,list}, unique]),
2168          H2 = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1]),
2169          {qlc,_,[{generate,_,{list,[3,4]}},
2170                  {generate,_,{qlc,_,
2171                               [{generate,_,{list,[a,b]}},
2172                                {generate,_,
2173                                 {qlc,_,[{generate,_,{table,{ets,table,_}}}],
2174                                  [{cache,list},{unique,true}]}}],
2175                               [{cache,list},{unique,true}]}}], []} = i(H2),
2176          L1s = [[{X,Y} || Y <- [a,b], X <- Xs] || Xs <- [[1,2], [2,1]]],
2177          L2s = [[{X,Y,Z} || X <- [3,4], {Y,Z} <- L1] || L1 <- L1s],
2178          R1 = qlc:e(H2),
2179          R2 = qlc:e(H2, {max_list_size, 0}), % on temporary file
2180          ets:delete(E),
2181          true = lists:member(R1, L2s),
2182          true = R1 =:= R2">>,
2183
2184       <<"E = ets:new(t, [duplicate_bag]),
2185          true = ets:insert(E, [{2},{1},{2}]),
2186          H1 = qlc:q([{X,Y} ||
2187                         Y <- [a,b],
2188                         {X} <- ets:table(E)],
2189                     [{cache,list}]),
2190          H2 = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1]),
2191          L1s = [[{X,Y} || Y <- [a,b], X <- Xs] || Xs <- [[1,2,2], [2,2,1]]],
2192          L2s = [[{X,Y,Z} || X <- [3,4], {Y,Z} <- L1] || L1 <- L1s],
2193          R1 = qlc:e(H2),
2194          R2 = qlc:e(H2, {max_list_size, 0}), % on temporary file
2195          ets:delete(E),
2196          true = lists:member(R1, L2s),
2197          true = R1 =:= R2">>,
2198
2199       <<"Q1 = qlc:q([{X,Y} ||
2200                         Y <- [a,b],
2201                         {X,_} <- qlc_SUITE:table_error([{a,1}], 2, err)],
2202                     [{cache,list}, unique]),
2203          Q = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- Q1]),
2204          {qlc,_,[{generate,_,{list,[3,4]}},
2205                  {generate,_,{qlc,_,
2206                               [{generate,_,{list,[a,b]}},
2207                                {generate,_,{table,_}}],
2208                               [{cache,list},{unique,true}]}}],
2209           []} = i(Q),
2210          err = qlc:e(Q,{max_list_size,0})">>,
2211
2212       begin
2213       Privdir = ?privdir,
2214       [<<"
2215          E = ets:new(t, [duplicate_bag]),
2216          N = 17000,
2217          true = ets:insert(E, [{X,X} || X <- lists:seq(1, N)]),
2218          N = ets:info(E, size),
2219          RF = fun(GOpts) ->
2220                       F = fun(CU) ->
2221                                   H1 = qlc:q([{X,Y} ||
2222                                                  Y <- [a,b],
2223                                                  {X,_} <- ets:table(E)],
2224                                              CU),
2225                                   qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1])
2226                           end,
2227                       Q1 = F([{cache,list}, unique]),
2228                       _ = qlc:info(Q1, GOpts),
2229                       R1 = qlc:e(Q1, GOpts),
2230                       Q2 = F([unique]),
2231                       R2 = qlc:e(Q2, GOpts),
2232                       true = lists:sort(R1) =:= lists:sort(R2)
2233               end,
2234          GOpts = [{tmpdir,\"">>,Privdir,<<"\"}],
2235          RF([{max_list_size, 1 bsl 35} | GOpts]),
2236          RF(GOpts),
2237          RF([{max_list_size, 40000} | GOpts]),
2238          true = ets:insert(E, [{X,X} || X <- lists:seq(1, N)]),
2239          true = N+N =:= ets:info(E, size),
2240          RF([{max_list_size, 1 bsl 30} | GOpts]),
2241          RF(GOpts),
2242          RF([{max_list_size, 40000} | GOpts]),
2243          ets:delete(E)">>]
2244       end,
2245
2246       <<"%% Temporary file employed.
2247          etsc(fun(E) ->
2248                       Q0 = qlc:q([X || X <- ets:table(E),
2249                                        begin element(1, X) > 5 end],
2250                                  {cache,list}),
2251                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2252                                                       Y <- Q0]),
2253                       R = [{X,Y} || X <- lists:seq(1, 5),
2254                                     Y <- lists:seq(6, 10)],
2255                       R = lists:sort(qlc:e(Q, {max_list_size, 100*1024}))
2256               end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
2257                                        I <- lists:seq(1, 10)])">>,
2258
2259       <<"%% Temporary file employed. The file is removed after error.
2260          L = [{I,a,lists:duplicate(100000,1)} || I <- lists:seq(1, 10)],
2261          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2262                           begin element(1, X) > 5 end],
2263                     {cache,list}),
2264          Q = qlc:q([{X, element(1,Y)} ||
2265                        X <- lists:seq(1, 5),
2266                        Y <- Q0]),
2267          err = qlc:e(Q)">>,
2268
2269       <<"%% Temporary file employed. The file is removed after error.
2270          L = [{I,a,lists:duplicate(100000,1)} || I <- lists:seq(1, 10)],
2271          Q0 = qlc:q([X || X <- qlc_SUITE:table(L, 1, []),
2272                           begin element(1, X) > 5 end],
2273                     {cache,list}),
2274          Q = qlc:q([{X, element(1,Y)} ||
2275                        X <- lists:seq(1, 5),
2276                        Y <- Q0]),
2277          {error, _, {file_error,_,_}} = qlc:e(Q, {tmpdir, \"/a/b/c\"})">>,
2278
2279       <<"Q = qlc:q([X || X <- [1,2]]),
2280          {'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, -1}))">>,
2281
2282       <<"Q = qlc:q([X || X <- [1,2]]),
2283          {'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, foo}))">>
2284
2285       ],
2286    run(Config, Ts),
2287    ok.
2288
2289%% Filters and match specs.
2290filter(Config) when is_list(Config) ->
2291    Ts = [
2292       <<"L = [1,2,3,4,5],
2293          QH1 = qlc:q([X || X <- L, X > 1, X < 4]),
2294          [2,3] = qlc:e(QH1),
2295          {list,{list,L},_MS} = i(QH1)
2296         ">>,
2297
2298       <<"L = [1,2,3,4,5],
2299          QH2 = qlc:q([X || X <- L, X > 1, X < 4, X > 2]),
2300          [3] = qlc:e(QH2),
2301          {list,{list,L},_MS} = i(QH2)
2302         ">>,
2303
2304          %% "X > 1" is skipped since the matchspec does the job
2305       <<"QH3 = qlc:q([X || X <- [1,2,3,4,5], X > 1, begin X < 4 end]),
2306          [2,3] = qlc:e(QH3),
2307          {qlc,_,[{generate,_,{list,{list,[1,2,3,4,5]},_MS}},_],[]} = i(QH3)
2308         ">>,
2309
2310       <<"QH4 = qlc:q([{X,Y} || X <- [1,2], Y <- [1,2]]),
2311          [{1,1},{1,2},{2,1},{2,2}] = qlc:e(QH4),
2312          {qlc,_,[{generate,_,{list,[1,2]}},{generate,_,{list,[1,2]}}],[]} =
2313              i(QH4)">>,
2314
2315          %% "X > 1" is skipped since the matchspec does the job
2316       <<"QH5 = qlc:q([{X,Y} || X <- [1,2], X > 1, Y <- [1,2]]),
2317          [{2,1},{2,2}] = qlc:e(QH5),
2318          {qlc,_,[{generate,_,{list,{list,[1,2]},_MS}},
2319                  {generate,_,{list,[1,2]}}],[]} =
2320              i(QH5)">>,
2321
2322       <<"%% Binaries are not handled at all when trying to find lookup values
2323          etsc(fun(E) ->
2324                      A = 2,
2325                      Q = qlc:q([X || {X} <- ets:table(E), <<A>> =:= <<X>>]),
2326                      [2] = lists:sort(qlc:e(Q)),
2327                      false = lookup_keys(Q)
2328              end, [{1},{2},{3}])">>,
2329
2330       <<"etsc(fun(E) ->
2331                      Q = qlc:q([X || {X,_} <- ets:table(E),
2332                                   qlc:e(qlc:q([Y || {Y,_} <- ets:table(E),
2333                                                              Y > X])) == []]),
2334                      [3] = qlc:e(Q)
2335              end, [{1,a},{2,b},{3,c}])">>,
2336
2337       <<"Q = qlc:q([X || {X} <- [], (false or (X/0 > 3))]),
2338          \"[]\" = qlc:info(Q),
2339          [] = qlc:e(Q)">>,
2340
2341       <<"%% match spec
2342          [] = qlc:e(qlc:q([X || {X} <- [{1},{2}],
2343                                 (false orelse (X/0 > 3))])),
2344          %% generated code
2345          {'EXIT', {badarith, _}} =
2346            (catch qlc:e(qlc:q([X || {X} <- [{1}],
2347                                     begin (false orelse (X/0 > 3)) end])))">>,
2348
2349       <<"%% Partial evaluation in filter.
2350          etsc(fun(E) ->
2351                     QH = qlc:q([{X+1,Y} || {X,Y} <- ets:table(E),
2352                                            X =:= 1-1+1+(+1)]),
2353                     [{3,2}] = qlc:e(QH),
2354                     [2] = lookup_keys(QH)
2355              end, [{1,1},{2,2},{3,3}])">>,
2356
2357       <<"%% =/2 in filters must not be recognized when 'badmatch' is
2358          %% possible.
2359          etsc(fun(E) ->
2360                     QH = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2361                                          ((Y = X) =:= 3)]),
2362                     {'EXIT', {{badmatch,4},_}} = (catch qlc:e(QH)),
2363                     false = lookup_keys(QH)
2364               end, [{3,3},{4,true}])">>,
2365
2366       <<"%% One more of the same kind.
2367          etsc(fun(E) ->
2368                      QH = qlc:q([{X,Y} || {X,_} <- ets:table(E),
2369                                           (Y=X) =:= (Y=1+1)]),
2370                      {'EXIT', {{badmatch,2},_}} = (catch qlc:e(QH)),
2371                      false = lookup_keys(QH)
2372              end, [{1,1},{2,2},{3,3}])">>,
2373
2374       <<"%% OTP-5195. Used to return a value, but badarith is correct.
2375          etsc(fun(E) ->
2376                      QH = qlc:q([X || {X,_} <- ets:table(E),
2377                                       (X =:= 1) and
2378                                    if X =:= 1 -> true;
2379                                       true -> X/0
2380                                    end]),
2381                      {'EXIT',{badarith,_}} = (catch qlc:e(QH)),
2382                      false = lookup_keys(QH)
2383              end, [{1,1},{2,2},{3,3}])">>,
2384
2385       <<"fun(Z) ->
2386            Q = qlc:q([X || Z < 2, X <- [1,2,3]]),
2387            [] = qlc:e(Q)
2388          end(3)">>,
2389
2390       <<"H = qlc:q([{P1,A,P2,B,P3,C} ||
2391                  P1={A,_} <- [{1,a},{2,b}],
2392                  {_,B}=P2 <- [{1,a},{2,b}],
2393                  C=P3 <- [1],
2394                  {[X,_],{_,X}} <- [{[1,2],{3,1}}, {[a,b],{3,4}}],
2395                  A > 0,
2396                  B =/= c,
2397                  C > 0]),
2398          L = [{{1,a},1,{1,a},a,1,1}, {{1,a},1,{2,b},b,1,1},
2399               {{2,b},2,{1,a},a,1,1}, {{2,b},2,{2,b},b,1,1}],
2400          L = qlc:e(H)">>,
2401
2402       <<"H = qlc:q([{X,Y} ||
2403                  X = _ <- [1,2,3],
2404                  _ = Y <- [a,b,c],
2405                  _ = _ <- [foo],
2406                  X > 1,
2407                  Y =/= a]),
2408          [{2,b},{2,c},{3,b},{3,c}] = qlc:e(H)">>
2409
2410       ],
2411    run(Config, Ts),
2412    ok.
2413
2414%% info/2.
2415info(Config) when is_list(Config) ->
2416    Ts = [
2417       <<"{list, [1,2]} = i(qlc:q([X || X <- [1,2]])),
2418          {append,[{list, [1,2]}, {list, [3,4]}]} =
2419               i(qlc:append([1,2],[3,4])),
2420          {sort,{list, [1,2]},[]} = i(qlc:sort([1,2])),
2421          E = ets:new(foo, []),
2422          ets:insert(E, [{1},{2}]),
2423          {table, _} = i(ets:table(E)),
2424          true = ets:delete(E),
2425          {list, [1,2]} = i([1,2]),
2426          {append, [{list, [1,2]}, {list, [3,4]}]} =
2427             i(qlc:q([X || X <- qlc:append([1,2],[3,4])])),
2428
2429          H0 = qlc:q([X || X <- throw({throw,t})]),
2430          {throw,t} = (catch {any_term,qlc:info(H0)}),
2431          {'EXIT', {badarg, _}} =
2432               (catch qlc:info(foobar)),
2433          {'EXIT', {badarg, _}} =
2434               (catch qlc:info(qlc:q([X || X <- [1,2]]), badarg))">>,
2435
2436       <<"{'EXIT', {badarg, _}} =
2437               (catch qlc:info([X || {X} <- []], {n_elements, 0})),
2438          L = lists:seq(1, 1000),
2439          \"[1,2,3,4,5,6,7,8,9,10|'...']\" = qlc:info(L, {n_elements, 10}),
2440          {cons,A1,{integer,A2,1},{atom,A3,'...'}} =
2441            qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
2442          1 = erl_anno:line(A1),
2443          1 = erl_anno:line(A2),
2444          1 = erl_anno:line(A3),
2445          Q = qlc:q([{X} || X <- [a,b,c,d,e,f]]),
2446          {call,_,_,[{cons,_,{atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},
2447                                                            {atom,_,'...'}}}},
2448                     {call,_,_,_}]} =
2449          qlc:info(Q, [{n_elements, 3},{format,abstract_code}]),
2450          \"ets:match_spec_run([a,b,c,d,e,f],\n\"
2451          \"                   ets:match_spec_compile([{'$1',[true],\"
2452          \"[{{'$1'}}]}]))\" =
2453             qlc:info(Q, [{n_elements, infinity}])">>,
2454
2455       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [1,2]])]),
2456          {qlc, _, [{generate, _, {list, [1,2]}}],[]} = i(Q1),
2457          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [1,2]])]),
2458          {list,{list,[1,2]},_} = i(Q2),
2459          [{1},{2}] = qlc:eval(Q2),
2460          Q3 = qlc:q([{X,Y} || X <- qlc:q([X || X <- [a,b]]),
2461                               Y <- qlc:q([Z || Z <- [a,b]])]),
2462          {qlc, _, [{generate, _, {list, [a,b]}},
2463                    {generate, _, {list, [a,b]}}], []} = i(Q3),
2464          Q4 = qlc:q([X || X <- [a]]),
2465          {list, [a]} = i(Q4),
2466          Q5 = qlc:q([X || X <- qlc:q([Y || Y <- [a,b]], unique)]),
2467          {qlc, _, [{generate, _, {list, [a,b]}}], [{unique,true}]} =
2468             i(Q5)">>,
2469
2470       <<"H = qlc:q([X || X <- qlc:append([qlc:q([X || X <- [1,2]]),[1,2]])]),
2471          {append, [{list, [1,2]},{list, [1,2]}]} = i(H),
2472          [1,2,1,2] = qlc:e(H)">>,
2473
2474       <<"H = qlc:q([{X} || X <- [], X > 1]),
2475          {list, []} = i(H),
2476          [] = qlc:e(H)">>,
2477
2478       <<"H1 = qlc:q([{X} || X <- [], X > 1]),
2479          H = qlc:q([{X} || X <- H1, X < 10]),
2480          {list, []} = i(H),
2481          [] = qlc:e(H)">>,
2482
2483       <<"L = [1,2,3],
2484          QH1 = qlc:q([{X} || X <- L, X > 1]),
2485          QH2 = qlc:q([{X} || X <- QH1]),
2486          [{{2}},{{3}}] = qlc:e(QH2),
2487          {list,{list,{list,L},_},_} = i(QH2)">>,
2488
2489       <<"H = qlc:q([X || X <- qlc:q([Y || Y <- qlc:q([Z || Z <-[1,2,1]])])]),
2490          {list, [1,2,1]} = i(H),
2491          [1,2,1] = qlc:eval(H)">>,
2492
2493       <<"%% Used to replace empty ETS tables with [], but that won't work.
2494          E = ets:new(apa,[]),
2495          QH1 = qlc:q([{X} || X <- ets:table(E), X > 1]),
2496          QH2 = qlc:q([{X} || X <- QH1], cache),
2497          [] = qlc:e(QH2),
2498          {qlc,_,[{generate,_,{table,{ets,table,_}}}],[]} = i(QH2),
2499          ets:delete(E)">>,
2500
2501       <<"Q1 = qlc:q([W || W <- [a,b]]),
2502          Q2 = qlc:q([Z || Z <- qlc:sort([55296,56296,57296])], unique),
2503          Q3 = qlc:q([{X,Y} || X <- qlc:keysort([2], [{1,a}]),
2504                               Y <- qlc:append([Q1, Q2]),
2505                               X > Y]),
2506          {qlc, T1,
2507           [{generate, P1, {list, [{1,a}]}},
2508            {generate, P2, {append, [{list, [a,b]},
2509                                    {qlc, T2, [{generate, P3,
2510                                                {sort, {list,[55296,56296,57296]},[]}}],
2511                                     [{cache,ets},{unique,true}]}]}},F],
2512           []} = i(Q3, cache_all),
2513          {tuple, _, [{var,_,'X'}, {var,_,'Y'}]} = binary_to_term(T1),
2514          {var, _, 'X'} = binary_to_term(P1),
2515          {var, _, 'Y'} = binary_to_term(P2),
2516          {var, _, 'Z'} = binary_to_term(P3),
2517          {var, _, 'Z'} = binary_to_term(T2),
2518          {op, _, '>', {var, _, 'X'}, {var, _, 'Y'}} = binary_to_term(F),
2519          true = binary_to_list(<<
2520           \"beginV1=qlc:q([Z||Z<-qlc:sort([55296,56296,57296],[])],[{unique,true}]),\"
2521           \"qlc:q([{X,Y}||X<-[{1,a}],Y<-qlc:append([[a,b],V1]),X>Y])end\"
2522              >>) == format_info(Q3, true)">>,
2523
2524       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [a,b]])]),
2525          {qlc, _, [{generate, _, {list, [a,b]}}], []} = i(Q1),
2526          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [a,b]])]),
2527          {list,{list,[a,b]},_} = i(Q2),
2528          [{a},{b}] = qlc:eval(Q2)">>,
2529
2530       <<"Q = qlc:keysort(2, [{1,a,b},{2,b,c},{3,4,c}]),
2531          {keysort,{list,[{1,a,b},{2,b,c},{3,4,c}]},2,[]} = i(Q),
2532          true = binary_to_list(<<
2533             \"qlc:keysort(2,[{1,a,b},{2,b,c},{3,4,c}],[])\">>)
2534              == format_info(Q, true),
2535          [{3,4,c},{1,a,b},{2,b,c}] = qlc:e(Q)">>,
2536
2537       <<"E = ets:new(foo, []),
2538          ets:insert(E, [{1},{2}]),
2539          Q = qlc_SUITE:default_table(E),
2540          {table,{'$MOD','$FUN',[]}} = i(Q),
2541          true = binary_to_list(<<\"'$MOD':'$FUN'()\">>)
2542                == format_info(Q, true),
2543          true = ets:delete(E)">>,
2544
2545       <<"\"[]\" = qlc:info([], flat),
2546          \"[]\" = qlc:info([]),
2547          \"[]\" = qlc:info([], {flat, true})">>,
2548
2549       <<"H = qlc:q([{X} || X <- [a,b]]),
2550         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2551                format_info(H, true),
2552         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2553                format_info(H, false)">>,
2554
2555       <<"H = qlc:q([{X} || X <- [a,b], begin true end]),
2556          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2557             == format_info(H, true),
2558          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2559             == format_info(H, false)">>,
2560
2561       <<"H = qlc:q([A || {A} <- [{1},{2}], (A =:= 2) andalso true]),
2562          {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} =
2563             qlc:info(H, {format,abstract_code})">>,
2564
2565       <<"H = qlc:q([{X} || X <- qlc:q([{X} || X <- [a,b], begin true end],
2566                                       unique),
2567                            begin true end]),
2568          true = binary_to_list(<<
2569         \"beginV1=qlc:q([{X}||X<-[a,b],begintrueend],[{unique,true}]),\"
2570         \"qlc:q([{X}||X<-V1,begintrueend])end\">>) ==
2571              format_info(H, true),
2572          true = binary_to_list(<<
2573         \"qlc:q([{X}||X<-qlc:q([{X}||X<-[a,b],begintrueend],\"
2574         \"[{unique,true}]),begintrueend])\">>) == format_info(H, false)">>,
2575
2576       <<"H0 = qlc:q([{V3} || V3 <- qlc:q([{V1} || V1 <- [a,b],
2577                                                   begin true end], unique),
2578                              begin true end]),
2579          H = qlc:sort(H0),
2580          true = binary_to_list(<<
2581          \"qlc:sort(qlc:q([{V3}||V3<-qlc:q([{V1}||\"
2582          \"V1<-[a,b],begintrueend],[{unique,true}]),begintrueend]),[])\">>)
2583              == format_info(H, false),
2584          true = binary_to_list(<<
2585          \"beginV2=qlc:q([{V1}||V1<-[a,b],begintrueend],[{unique,true}]),\"
2586          \"V4=qlc:q([{V3}||V3<-V2,begintrueend]),qlc:sort(V4,[])end\">>)
2587              == format_info(H, true)">>,
2588
2589       <<"H0 = qlc:q([X || X <- [true], begin true end]),
2590          H1 = qlc:q([{X} || X <- [a,b], begin true end],
2591                     [{unique,begin [T] = qlc:e(H0), T end}]),
2592          {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},
2593                  [{lc,_,{tuple,_,[{var,_,'X'}]},
2594                         [{generate,_,{var,_,'X'},
2595                                      {cons,_,{atom,_,a},_}},
2596                          {block, _, [{atom, _, true}]}]},
2597                   {cons,_,_,_}]} = i(H1, {format, abstract_code})">>,
2598
2599       <<"E = ets:new(apa, [duplicate_bag]),
2600          true = ets:insert(E, [{1,a},{2,b},{3,c},{4,d}]),
2601          QH = qlc:q([X || {X,_} <- ets:tab2list(E), X > 2], unique),
2602          {qlc, _, [{generate, _, {list, _, _MS}}], [{unique, true}]} =
2603                i(QH),
2604          [3,4] = lists:sort(qlc:e(QH)),
2605          ets:delete(E)">>,
2606
2607       %% "Imported" variable.
2608       <<"F = fun(U) -> qlc:q([{X} || X <- [1,2,3,4,5,6], X > U]) end,
2609          QH = F(4),
2610          {call, _ ,
2611                {remote, _, {atom, _, ets},{atom, _, match_spec_run}},
2612                [{string, _, [1,2,3,4,5,6]},
2613                 {call, _,
2614                       _compile,
2615                       [{cons, _,
2616                              {tuple, _,
2617                                     [{atom, _,'$1'},
2618                                      {cons, _,
2619                                            {tuple,
2620                                                 _,
2621                                                [{atom, _,'>'},
2622                                                 {atom, _,'$1'},
2623                                                 {tuple,
2624                                                      _,
2625                                                     [{atom, _,const},
2626                                                      {integer, _,4}]}]},
2627                                            _},
2628                                      {cons, _, _, _}]},
2629                              {nil,_}}]}]} = i(QH, {format, abstract_code}),
2630          [{5},{6}] = qlc:e(QH),
2631          [{4},{5},{6}] = qlc:e(F(3))">>,
2632
2633          <<"Fun = fun ?MODULE:i/2,
2634             L = [{#{k => #{v => Fun}}, Fun}],
2635             H = qlc:q([Q || Q <- L, Q =:= {#{k => #{v => Fun}}, Fun}]),
2636             L = qlc:e(H),
2637             {call,_,_,[{lc,_,{var,_,'Q'},
2638                         [{generate,_,_,_},
2639                          {op,_,_,_,_}]}]} =
2640                qlc:info(H, [{format,abstract_code}])">>
2641
2642       ],
2643    run(Config, Ts),
2644    ok.
2645
2646%% Nested QLC expressions. QLC expressions in filter and template.
2647nested_info(Config) when is_list(Config) ->
2648    Ts = [
2649       <<"L = [{1,a},{2,b},{3,c}],
2650          Q = qlc:q(
2651                [{X,R} ||
2652                    {X,_} <- qlc_SUITE:table(L, []),
2653                    begin % X imported
2654                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2655                                                    <- qlc_SUITE:table(L, []),
2656                                                  Y > X])),
2657                        true
2658                    end]),
2659          true = binary_to_list(<<
2660            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2661            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),Y>X]))\"
2662            \",trueend])\">>) == format_info(Q, true),
2663          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2664
2665       <<"L = [{1,a},{2,b},{3,c}],
2666          Q = qlc:q( % X imported
2667                [{X,qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2668                                          Y > X]))} ||
2669                    {X,_} <- qlc_SUITE:table(L, [])]),
2670          true = binary_to_list(<<
2671            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2672            \"Y>X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2673              == format_info(Q, true),
2674          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2675
2676       <<"L = [{1,a},{2,b},{3,c}],
2677          Q = qlc:q(
2678                [{X,R} ||
2679                    {X,_} <- qlc_SUITE:table(L, []),
2680                    begin % X imported
2681                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2682                                                    <- qlc_SUITE:table(L, []),
2683                                                  Y =:= X])),
2684                        true
2685                    end]),
2686          true = binary_to_list(<<
2687            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2688            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2689            \"Y=:=X])),trueend])\">>) == format_info(Q, true),
2690          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2691
2692       <<"L = [{1,a},{2,b},{3,c}],
2693          Q = qlc:q(
2694                [{X, % X imported
2695                  qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2696                                        Y =:= X]))} ||
2697                    {X,_} <- qlc_SUITE:table(L, [])]),
2698          true = binary_to_list(<<
2699            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2700            \"Y=:=X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2701             == format_info(Q, true),
2702          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2703
2704       <<"L = [{1,a},{2,b},{3,c}],
2705          Q = qlc:q(
2706                [{X,R} ||
2707                    {X,_} <- qlc_SUITE:table(L, []),
2708                    begin
2709                        R = qlc:e(qlc:q([Y || Y <- [X]])),
2710                        true
2711                    end]),
2712          true = binary_to_list(<<
2713            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2714            \"beginR=qlc:e(qlc:q([Y||Y<-[X]])),trueend])\">>)
2715             == format_info(Q, true),
2716          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2717
2718       <<"L = [{1,a},{2,b},{3,c}],
2719          Q = qlc:q(
2720                [{X,qlc:e(qlc:q([Y || Y <- [X]]))} ||
2721                    {X,_} <- qlc_SUITE:table(L, [])]),
2722          true = binary_to_list(<<
2723            \"qlc:q([{X,qlc:e(qlc:q([Y||Y<-[X]]))}||{X,_}<-qlc_SUITE:\"
2724            \"the_list([{1,a},{2,b},{3,c}])])\">>) == format_info(Q, true),
2725          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2726
2727       <<"L = [{1,a},{2,b}],
2728          Q = qlc:q(
2729                [{X,Y} ||
2730                    {X,_} <- qlc_SUITE:table(L, []),
2731                    {Y,_} <- qlc:q(
2732                               [{Z,V} ||
2733                                   {Z,_} <- qlc_SUITE:table(L, []),
2734                                   {V} <- qlc:q(
2735                                              [{W} || W
2736                                                  <- qlc_SUITE:table(L, [])])
2737                                      ])
2738                       ]),
2739          true = binary_to_list(<<
2740           \"beginV1=qlc:q([{W}||W<-qlc_SUITE:the_list([{1,a},{2,b}])]),\"
2741           \"V2=qlc:q([{Z,V}||{Z,_}<-qlc_SUITE:the_list([{1,a},{2,b}]),\"
2742           \"{V}<-V1]),qlc:q([{X,Y}||{X,_}<-qlc_SUITE:the_list([{1,a},\"
2743           \"{2,b}]),{Y,_}<-V2])end\">>) == format_info(Q, true),
2744          [{1,1},{1,1},{1,2},{1,2},{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>
2745
2746       ],
2747    run(Config, Ts),
2748    ok.
2749
2750
2751%% Lookup keys. Mostly test of patterns.
2752lookup1(Config) when is_list(Config) ->
2753    Ts = [
2754       <<"etsc(fun(E) ->
2755                Q = qlc:q([A || {A=3} <- ets:table(E)]),
2756                [3] = qlc:eval(Q),
2757                [3] = lookup_keys(Q)
2758          end, [{1},{2},{3},{4}])">>,
2759
2760       <<"etsc(fun(E) ->
2761                Q = qlc:q([A || {A=3} <- ets:table(E)],{max_lookup,0}),
2762                [3] = qlc:eval(Q),
2763                false = lookup_keys(Q)
2764          end, [{1},{2},{3},{4}])">>,
2765
2766       <<"%% The lookup and max_lookup options interact.
2767          etsc(fun(E) ->
2768                Q = qlc:q([X || {X} <- ets:table(E),
2769                                (X =:= 1) or (X =:= 2)],
2770                          [{lookup,true},{max_lookup,1}]),
2771                {'EXIT', {no_lookup_to_carry_out, _}} = (catch qlc:e(Q))
2772         end, [{1},{2}])">>,
2773
2774       <<"etsc(fun(E) ->
2775                Q = qlc:q([{A,B,C,D} || {A,B}={C,D} <- ets:table(E)]),
2776                [{1,2,1,2},{3,4,3,4}] = lists:sort(qlc:eval(Q)),
2777                false = lookup_keys(Q)
2778          end, [{1,2},{3,4}])">>,
2779
2780       <<"etsc(fun(E) ->
2781                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E)]),
2782                [{1,1,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
2783                false = lookup_keys(Q)
2784          end, [{1,2},{2,2},{1,1}])">>,
2785
2786       <<"etsc(fun(E) ->
2787                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2788                                      (D =:= 2) or (B =:= 1)],
2789                          {max_lookup,infinity}),
2790                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2791                [1,2] = lookup_keys(Q)
2792         end, [{1,2},{2,2},{1,1}])">>,
2793
2794       <<"etsc(fun(E) ->
2795                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2796                                      (D =:= 2) xor (B =:= 1)]),
2797                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2798                [1,2] = lookup_keys(Q)
2799         end, [{1,2},{2,2},{1,1}])">>,
2800
2801       <<"etsc(fun(E) ->
2802                Q = qlc:q([3 || {{[3,4],apa}} <- ets:table(E)]),
2803                [3] = qlc:e(Q),
2804                [{[3,4],apa}] = lookup_keys(Q)
2805        end, [{{[4,3],foo}},{{[3,4],apa}}])">>,
2806
2807       <<"etsc(fun(E) ->
2808                Q = qlc:q([3 || {3} <- ets:table(E)]),
2809                [3] = qlc:e(Q),
2810                [3] = lookup_keys(Q)
2811        end, [{2},{3},{4}])">>,
2812
2813       <<"etsc(fun(E) ->
2814                Q = qlc:q([{X,Y,Z} || {{X,_},Y,Y={_,Z},X,Y} <- ets:table(E)]),
2815                [] = qlc:e(Q),
2816                false = lookup_keys(Q)
2817        end, [{{1,1},1,{1,1},1,1}])">>,
2818
2819       <<"etsc(fun(E) ->
2820                Q = qlc:q([X || {X,X=2} <- ets:table(E)]),
2821                [2] = qlc:e(Q),
2822                [2] = lookup_keys(Q)
2823        end, [{2,2},{3,3}])">>,
2824
2825       <<"etsc(fun(E) ->
2826                Q = qlc:q([X || {{_,3}={4,_}=X} <- ets:table(E)]),
2827                [{4,3}] = qlc:e(Q),
2828                [{4,3}] = lookup_keys(Q)
2829        end, [{{2,3}},{{4,3}}])">>,
2830
2831       <<"U = 17.0,
2832          etsc(fun(E) ->
2833                Q = qlc:q([X || {_=X=_} <- ets:table(E)]),
2834                [U] = qlc:e(Q),
2835                false = lookup_keys(Q)
2836        end, [{U},{U+U,U}])">>,
2837
2838       <<"etsc(fun(E) ->
2839                Q = qlc:q([{X,Y,Z,W} || {X=Y}=Z={V=W} <- ets:table(E),
2840                                        V == {h,g}]),
2841                [{{h,g},{h,g},{{h,g}},{h,g}}] = qlc:e(Q),
2842                [{h,g}] = lookup_keys(Q)
2843        end, [{h,g},{{h,g}}])">>,
2844
2845       <<"etsc(fun(E) ->
2846                Q = qlc:q([{C,Y,Z,X} || {{X=Y}=Z}={{A=B}=C} <- ets:table(E),
2847                                        A == a, B =/= c]),
2848                [{{a},a,{a},a}] = qlc:e(Q),
2849                [{a}] = lookup_keys(Q)
2850        end, [{{1}},{{a}}])">>,
2851
2852       <<"etsc(fun(E) ->
2853               Q = qlc:q([{A,D,Y,X} ||
2854                             {{A={B=C}},{D={C}}} = {X,Y} <- ets:table(E),
2855                             [] == B]),
2856                [{{[]},{[]},{{[]}},{{[]}}}] = qlc:e(Q),
2857                [{{[]}}] = lookup_keys(Q)
2858        end, [{{{[]}},{{[]}}}])">>,
2859
2860       {cres,
2861        <<"etsc(fun(E) ->
2862                 Q = qlc:q([X || {X}=X <- ets:table(E)]),
2863                 [] = qlc:e(Q),
2864                 false = lookup_keys(Q)
2865         end, [{1},{a}])">>,
2866        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
2867        []},
2868
2869       <<"etsc(fun(E) ->
2870                Q = qlc:q([X || {X=X,Y=Y}={Y=Y,X=X} <- ets:table(E),
2871                                {} == X]),
2872                [{}] = qlc:e(Q),
2873                [{}] = lookup_keys(Q)
2874        end, [{{},{}},{[],[]}])">>,
2875
2876       <<"etsc(fun(E) ->
2877                Q = qlc:q([X || {3+4=7,X} <- ets:table(E),
2878                                X =:= 3+997]),
2879                [1000] = qlc:e(Q),
2880                [7] = lookup_keys(Q)
2881        end, [{7,1000},{8,1000}])">>,
2882
2883       <<"etsc(fun(E) ->
2884                Q = qlc:q([{X, Y} || [X]=[Y] <- ets:table(E)]),
2885                [] = qlc:eval(Q),
2886                false = lookup_keys(Q)
2887        end, [{a}])">>,
2888
2889       {cres,
2890        <<"etsc(fun(E) ->
2891                 Q = qlc:q([X || X={1,2,3,X,5} <- ets:table(E)]),
2892                 [] = qlc:e(Q),
2893                 false = lookup_keys(Q)
2894         end, [{a},{b}])">>,
2895        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2896        []},
2897
2898       {cres,
2899        <<"etsc(fun(E) ->
2900                 Q = qlc:q([X || X=[1,2,3,X,5] <- ets:table(E)]),
2901                 [] = qlc:e(Q),
2902                 false = lookup_keys(Q)
2903         end, [{a},{b}])">>,
2904        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2905        []},
2906
2907       <<"etsc(fun(E) ->
2908                Q = qlc:q([X || X = <<X>> <- ets:table(E)]),
2909                [] = qlc:e(Q),
2910                false = lookup_keys(Q)
2911        end, [{a},{b}])">>,
2912
2913       <<"Tre = 3.0,
2914          etsc(fun(E) ->
2915                Q = qlc:q([{A,B} || {A,B}={{a,C},{a,C}} <- ets:table(E),
2916                                    C =:= Tre]),
2917                [] = qlc:e(Q),
2918                [{a,Tre}] = lookup_keys(Q)
2919        end, [{a,b}])">>,
2920
2921       <<"A = 3,
2922          etsc(fun(E) ->
2923                Q = qlc:q([X || X <- ets:table(E), A =:= element(1, X)]),
2924                [{3,3}] = qlc:e(Q),
2925                [3] = lookup_keys(Q)
2926        end, [{1,a},{3,3}])">>,
2927
2928       <<"A = 3,
2929          etsc(fun(E) ->
2930                Q = qlc:q([X || X <- ets:table(E), A =:= erlang:element(1, X)]),
2931                [{3,3}] = qlc:e(Q),
2932                [3] = lookup_keys(Q)
2933        end, [{1,a},{3,3}])">>,
2934
2935       <<"etsc(fun(E) ->
2936                A = 3,
2937                Q = qlc:q([X || X <- ets:table(E),
2938                                A == element(1,X),
2939                                element(1,X) =:= a]),
2940                [] = qlc:e(Q),
2941                [a] = lookup_keys(Q)
2942        end, [{a},{b},{c}])">>,
2943
2944       {cres,
2945        <<"etsc(fun(E) ->
2946                 Q = qlc:q([X || {X = {[a,Z]},
2947                                  Z = [foo, {[Y]}],
2948                                  Y = {{foo,[X]}}} <- ets:table(E)]),
2949                 [] = qlc:e(Q),
2950                 false = lookup_keys(Q)
2951         end, [{a,b,c},{d,e,f}])">>,
2952        %% {warnings,[{{2,34},qlc,nomatch_pattern}]}}
2953        []}
2954
2955       ],
2956    run(Config, Ts),
2957    ok.
2958
2959%% Lookup keys. Mostly test of filters.
2960lookup2(Config) when is_list(Config) ->
2961    Ts = [
2962       <<"%% Only guards are inspected. No lookup.
2963          etsc(fun(E) ->
2964                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2965                                     ((Y = X) =:= 3)]),
2966                 {'EXIT', {{badmatch,4},_}} = (catch qlc:e(Q))
2967         end, [{3,3},{4,true}])">>,
2968
2969       <<"%% Only guards are inspected. No lookup.
2970          etsc(fun(E) ->
2971                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2972                                     Y = (X =:= 3)]),
2973                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2974         end, [{false,3},{true,3}])">>,
2975
2976       <<"%% Only guards are inspected. No lookup.
2977          etsc(fun(E) ->
2978                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2979                                     Y = (X =:= 3)]),
2980                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2981         end, [{3,true},{4,true}])">>,
2982
2983       <<"%% Only guards are inspected. No lookup.
2984          E1 = ets:new(e, [ordered_set]),
2985          true = ets:insert(E1, [{1,1}, {2,2}, {3,3}, {4,4}, {5,5}]),
2986          E2 = ets:new(join, [ordered_set]),
2987          true = ets:insert(E2, [{true,1},{false,2}]),
2988          Q = qlc:q([{X,Z} || {_,X} <- ets:table(E1),
2989                              {Y,Z} <- ets:table(E2),
2990                              Y = (X =:= 3)]),
2991          {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q)),
2992          ets:delete(E1),
2993          ets:delete(E2)">>,
2994
2995       <<"etsc(fun(E) ->
2996                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2997                                      (A =:= 3) or (4 =:= D)]),
2998                [{3,3,3},{4,4,4}] = lists:sort(qlc:e(Q)),
2999                [3,4] = lookup_keys(Q)
3000        end, [{2,2},{3,3},{4,4}])">>,
3001
3002       <<"etsc(fun(E) ->
3003               Q = qlc:q([X || {X,U} <- ets:table(E), X =:= U]),
3004               [1] = qlc:e(Q),
3005               false = lookup_keys(Q)
3006       end, [{1,1}])">>,
3007
3008       {cres,
3009        <<"etsc(fun(E) ->
3010                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3011                                     {[X],4} =:= {[3],X}]),
3012                 [] = qlc:e(Q),
3013                 false = lookup_keys(Q)
3014         end, [{1}, {2}])">>,
3015        %% {warnings,[{{3,46},qlc,nomatch_filter}]}},
3016        []},
3017
3018       {cres,
3019        <<"etsc(fun(E) ->
3020                Q = qlc:q([X || {X} <- ets:table(E),
3021                                X == 1, X =:= 2]),
3022                [] = qlc:e(Q),
3023                false = lookup_keys(Q)
3024        end, [{1}, {2}])">>,
3025        %% {warnings,[{{3,43},qlc,nomatch_filter}]}},
3026        []},
3027
3028       {cres,
3029        <<"etsc(fun(E) ->
3030                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3031                                     {[X,Y],4} =:= {[3,X],X}]),
3032                 [] = qlc:e(Q),
3033                 false = lookup_keys(Q)
3034         end, [{1}, {2}])">>,
3035        %% {warnings,[{{3,48},qlc,nomatch_filter}]}},
3036        []},
3037
3038       <<"etsc(fun(E) ->
3039                Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
3040                                    ({X,3} =:= {Y,Y}) or (X =:= 4)]),
3041                [{3,3},{4,4}] = lists:sort(qlc:e(Q)),
3042                [3,4] = lookup_keys(Q)
3043        end, [{2,2},{3,3},{4,4},{5,5}])">>,
3044
3045       {cres,
3046        <<"etsc(fun(E) ->
3047                 Q = qlc:q([X || {X} <- ets:table(E), {[X]} =:= {[3,4]}]),
3048                 [] = qlc:e(Q),
3049                 false = lookup_keys(Q)
3050         end, [{[3]},{[3,4]}])">>,
3051        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3052        []},
3053
3054       <<"etsc(fun(E) ->
3055                U = 18,
3056                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E), [X|a] =:= [3|U]]),
3057                [] = qlc:e(Q),
3058                [3] = lookup_keys(Q)
3059        end, [{2}, {3}])">>,
3060
3061       <<"etsc(fun(E) ->
3062                U = 18, V = 19,
3063                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3064                                    [X|V] =:= [3|U+1]]),
3065                [{3,3}] = qlc:e(Q),
3066                [3] = lookup_keys(Q)
3067        end, [{2},{3}])">>,
3068
3069       <<"%% Blocks are not handled.
3070          etsc(fun(E) ->
3071                Q = qlc:q([X || {X} <- ets:table(E), begin X == a end]),
3072                [a] = qlc:e(Q),
3073                false = lookup_keys(Q)
3074        end, [{a},{b}])">>,
3075
3076       {cres,
3077        <<"etsc(fun(E) ->
3078                 Q = qlc:q([X || {X} <- ets:table(E),
3079                                 (3 =:= X) or (X =:= 12),
3080                                 (8 =:= X) or (X =:= 10)]),
3081                 [] = lists:sort(qlc:e(Q)),
3082                 false = lookup_keys(Q)
3083         end, [{2},{3},{4},{8}])">>,
3084        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3085        []},
3086
3087       {cres,
3088        <<"etsc(fun(E) ->
3089                 Q = qlc:q([X || {X} <- ets:table(E),
3090                                 ((3 =:= X) or (X =:= 12))
3091                                  and ((8 =:= X) or (X =:= 10))]),
3092                 [] = lists:sort(qlc:e(Q)),
3093                 false = lookup_keys(Q)
3094         end, [{2},{3},{4},{8}])">>,
3095        %% {warnings,[{{4,35},qlc,nomatch_filter}]}},
3096        []},
3097
3098       <<"F = fun(U) ->
3099                Q = qlc:q([X || {X} <- [a,b,c],
3100                                 X =:= if U -> true; true -> false end]),
3101                [] = qlc:eval(Q),
3102                false = lookup_keys(Q)
3103              end,
3104          F(apa)">>,
3105
3106       {cres,
3107        <<"etsc(fun(E) ->
3108                 Q = qlc:q([X || {X=1,X} <- ets:table(E), X =:= 2]),
3109                 [] = qlc:e(Q),
3110                 false = lookup_keys(Q)
3111           end, [{1,1},{2,1}])">>,
3112        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3113        []},
3114
3115       <<"Two = 2.0,
3116          etsc(fun(E) ->
3117                Q = qlc:q([X || {X} <- ets:table(E), X =:= Two]),
3118                [Two] = qlc:e(Q),
3119                [Two] = lookup_keys(Q)
3120        end, [{2.0},{2}])">>,
3121
3122       <<"etsc(fun(E) ->
3123                %% This float is equal (==) to an integer. Not a constant!
3124                Q = qlc:q([X || {X} <- ets:table(E), X == {a,b,c,[2.0]}]),
3125                [_,_] = qlc:e(Q),
3126                false = lookup_keys(Q)
3127        end, [{{a,b,c,[2]}},{{a,b,c,[2.0]}}])">>,
3128
3129       <<"%% Must _not_ regard floats as constants. Check imported variables
3130          %% in runtime.
3131          etsc(fun(E) ->
3132                U = 3.0,
3133                QH = qlc:q([X || {X,_} <- ets:table(E), X =:= U]),
3134                [] = qlc:e(QH),
3135                [U] = lookup_keys(QH)
3136        end, [{1,a},{2,b},{3,c},{4,d}])">>,
3137
3138       <<"etsc(fun(E) ->
3139                Q = qlc:q([X || {X} <- ets:table(E),
3140                                length(X) =:= 1]),
3141                [[1]] = qlc:e(Q),
3142                false = lookup_keys(Q)
3143        end, [{[1]},{[2,3]}])">>,
3144
3145       <<"etsc(fun(E) ->
3146                A=3,
3147                Q = qlc:q([X || {X,Y} <- ets:table(E), X =:= A, Y =:= 3]),
3148                [3] = qlc:e(Q),
3149                [3] = lookup_keys(Q)
3150        end, [{3,3},{4,3}])">>,
3151
3152       <<"etsc(fun(E) ->
3153                A = 1,
3154                Q = qlc:q([X || {X} <- ets:table(E),
3155                                X =:= 1, <<X>> =:= <<A>>]),
3156                [1] = qlc:e(Q),
3157                [1] = lookup_keys(Q)
3158        end, [{1},{2}])">>,
3159
3160       <<"etsc(fun(E) ->
3161                Q = qlc:q([X || {X} <- ets:table(E), X == a]),
3162                [a] = qlc:e(Q),
3163                [a] = lookup_keys(Q)
3164        end, [{a},{b},{c}])">>,
3165
3166       {cres,
3167        <<"etsc(fun(E) ->
3168                 Q = qlc:q([X || {X}=Y <- ets:table(E),
3169                                 element(2, Y) == b,
3170                                 X =:= 1]),
3171                 [] = qlc:e(Q),
3172                 false = lookup_keys(Q)
3173         end, [{1,b},{2,3}])">>,
3174        %% {warnings,[{2,sys_core_fold,nomatch_guard},
3175	%% 	   {3,qlc,nomatch_filter},
3176	%% 	   {3,sys_core_fold,{eval_failure,badarg}}]}},
3177        {warnings,[{2,sys_core_fold,nomatch_guard},
3178		   {3,sys_core_fold,{eval_failure,badarg}}]}},
3179
3180       <<"etsc(fun(E) ->
3181                Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
3182                [1] = qlc:e(Q),
3183                [1] = lookup_keys(Q)
3184        end, [{1}, {2}])">>,
3185
3186       <<"etsc(fun(E) ->
3187                Q = qlc:q([X || {X} <- ets:table(E), 1 =:= element(1,{X})]),
3188                [1] = qlc:e(Q),
3189                [1] = lookup_keys(Q)
3190        end, [{1}, {2}])">>,
3191
3192       {cres,
3193        <<"etsc(fun(E) ->
3194                 Q = qlc:q([X || {X} <- ets:table(E),
3195                                 X =:= {1},
3196                                 element(1,X) =:= 2]),
3197                 [] = qlc:e(Q),
3198                 false = lookup_keys(Q)
3199         end, [{{1}},{{2}}])">>,
3200        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3201        []},
3202
3203       {cres,
3204        <<"etsc(fun(E) ->
3205                 Q = qlc:q([X || {X} <- ets:table(E),
3206                                 X =:= {1},
3207                                 element(1,X) =:= element(1, {2})]),
3208                 [] = qlc:e(Q),
3209                 false = lookup_keys(Q)
3210         end, [{{1}},{{2}}])">>,
3211        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3212        []},
3213
3214       <<"etsc(fun(E) ->
3215                Q = qlc:q([X || {X} <- ets:table(E),
3216                                element(1,X) =:= 1, X =:= {1}]),
3217                [{1}] = qlc:e(Q),
3218                [{1}] = lookup_keys(Q)
3219        end, [{{1}},{{2}}])">>,
3220
3221       <<"etsc(fun(E) ->
3222                Q = qlc:q([X || {X} <- ets:table(E),
3223                                {{element(1,element(1,{{1}}))}} =:= {X}]),
3224                [{1}] = qlc:e(Q),
3225                [{1}] = lookup_keys(Q)
3226        end, [{{1}},{{2}}])">>,
3227
3228       <<"etsc(fun(E) ->
3229                Q = qlc:q([X || X <- ets:table(E),
3230                                {element(1,element(1, {{1}}))} =:=
3231                                      {element(1,X)}]),
3232                [{1}] = qlc:e(Q),
3233                [1] = lookup_keys(Q)
3234        end, [{1},{2}])">>,
3235
3236       <<"etsc(fun(E) ->
3237                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3238                                (X =:= 1) and (Y =:= 2)
3239                                    or (X =:= 3) and (Y =:= 4)]),
3240                [1,3] = lists:sort(qlc:e(Q)),
3241                [{1,2}, {3,4}] = lookup_keys(Q)
3242        end, [{{1,2}}, {{3,4}}, {{2,3}}])">>,
3243
3244       <<"etsc(fun(E) ->
3245                Q = qlc:q([X || {{X,a}} <- ets:table(E), X =:= 3]),
3246                [3] = qlc:e(Q),
3247                [{3,a}] = lookup_keys(Q)
3248        end, [{{3,a}},{{3,b}}])">>,
3249
3250       <<"etsc(fun(E) ->
3251                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3252                                X =:= 3, Y =:= a]),
3253                [3] = qlc:e(Q),
3254                [{3,a}] = lookup_keys(Q)
3255        end, [{{3,a},3}, {{4,a},3}])">>,
3256
3257       <<"etsc(fun(E) ->
3258                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3259                                (X =:= 3) and (Y =:= a)
3260                                   or (X =:= 4) and (Y =:= a)]),
3261                [3,4] = qlc:e(Q),
3262                [{3,a}, {4,a}] = lookup_keys(Q)
3263        end, [{{3,a},3}, {{4,a},3}])">>,
3264
3265       {cres,
3266        <<"etsc(fun(E) ->
3267                 Q = qlc:q([X || {X} <- ets:table(E),
3268                                 (X =:= 3) and (X =:= a)]),
3269                 [] = qlc:e(Q),
3270                 false = lookup_keys(Q)
3271         end, [{3}, {4}])">>,
3272        %% {warnings,[{{3,44},qlc,nomatch_filter}]}},
3273        []},
3274
3275       <<"etsc(fun(E) ->
3276                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3277                                X =:= 3, ((Y =:= a) or (Y =:= b))]),
3278                [3,3] = qlc:e(Q),
3279                [{3,a},{3,b}] = lists:sort(lookup_keys(Q))
3280        end, [{{3,a}},{{2,b}},{{3,b}}])">>,
3281
3282       <<"etsc(fun(E) ->
3283                Q = qlc:q([X || {X,Y} <- ets:table(E),
3284                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3285                [a] = qlc:e(Q),
3286                [a] = lookup_keys(Q)
3287        end, [{a,4},{3,3}])">>,
3288
3289       <<"etsc(fun(E) ->
3290                Q = qlc:q([X || {X,Y} <- ets:table(E),
3291                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3292                [3,a] = lists:sort(qlc:e(Q)),
3293                [3,a] = lookup_keys(Q)
3294        end, [{a,4},{3,3}])">>,
3295
3296       <<"etsc(fun(E) ->
3297                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3298                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3299                [3,a] = lists:sort(qlc:e(Q)),
3300                false = lookup_keys(Q)
3301        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3302
3303       <<"etsc(fun(E) ->
3304                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3305                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3306                [a] = lists:sort(qlc:e(Q)),
3307                [{a,4}] = lookup_keys(Q)
3308        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3309
3310        <<"etsc(fun(E) ->
3311                NoAnswers = 3*3*3+2*2*2,
3312                Q = qlc:q([{X,Y,Z} ||
3313                              {{X,Y,Z}} <- ets:table(E),
3314                              (((X =:= 4) or (X =:= 5)) and
3315                               ((Y =:= 4) or (Y =:= 5)) and
3316                               ((Z =:= 4) or (Z =:= 5))) or
3317                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3318                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3319                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3320                          {max_lookup, NoAnswers}),
3321                 {list, {table, _}, _} = i(Q),
3322                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3323                 true = NoAnswers =:= length(lookup_keys(Q))
3324         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3325
3326        <<"etsc(fun(E) ->
3327                Q = qlc:q([{X,Y,Z} ||
3328                              {{X,Y,Z}} <- ets:table(E),
3329                              (((X =:= 4) or (X =:= 5)) and
3330                               ((Y =:= 4) or (Y =:= 5)) and
3331                               ((Z =:= 4) or (Z =:= 5))) or
3332                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3333                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3334                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3335                          {max_lookup, 10}),
3336                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3337                 {table,{ets,table,[_,[{traverse,{select,_}}]]}} = i(Q)
3338         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3339
3340       <<"etsc(fun(E) ->
3341                Q = qlc:q([X || X={_,_,_} <- ets:table(E),
3342                                element(1, X) =:= 3, element(2, X) == a]),
3343                [{3,a,s}] = qlc:e(Q),
3344                [3] = lookup_keys(Q)
3345        end, [{1,c,q},{2,b,r},{3,a,s}])">>,
3346
3347       <<"etsc(fun(E) ->
3348                Q = qlc:q([X || X <- ets:table(E),
3349                                element(0, X) =:= 3]),
3350                [] = qlc:e(Q),
3351                false = lookup_keys(Q)
3352        end, [{1},{2}])">>,
3353
3354       <<"etsc(fun(E) ->
3355                F = fun(_) -> 3 end,
3356                %% No occurs check; X =:= F(X) is ignored.
3357                Q = qlc:q([X || {X} <- ets:table(E),
3358                                X =:= 3, X =:= F(X)]),
3359                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]} = i(Q),
3360                [3] = lists:sort(qlc:e(Q)),
3361                [3] = lookup_keys(Q)
3362        end, [{2},{3},{4}])">>,
3363
3364       <<"etsc(fun(E) ->
3365                A = a, B = a,
3366                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3367                                ((X =:= A) and (Y =:= B))
3368                                 or ((X =:= B) and (Y =:= A))]),
3369                [a] = qlc:e(Q),
3370                %% keys are usorted, duplicate removed:
3371                [{a,a}] = lookup_keys(Q)
3372        end, [{{a,a}},{{b,b}}])">>,
3373
3374       <<"etsc(fun(E) ->
3375                A = a, B = b,
3376                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3377                                ((X =:= A) and (Y =:= B))
3378                                 or ((X =:= B) and (Y =:= A))]),
3379                [a,b] = lists:sort(qlc:e(Q)),
3380                [{a,b},{b,a}] = lookup_keys(Q)
3381        end, [{{a,b}},{{b,a}},{{c,a}},{{d,b}}])">>,
3382
3383       %% The atom 'fail' is recognized - lookup.
3384       <<"etsc(fun(E) ->
3385                Q = qlc:q([A || {A} <- ets:table(E),
3386                                (A =:= 2)
3387                                    orelse fail
3388                                   ]),
3389                [2] = lists:sort(qlc:e(Q)),
3390                [2] = lookup_keys(Q)
3391           end, [{1},{2}])">>
3392
3393       ],
3394
3395    ok = run(Config, Ts),
3396
3397    TsR = [
3398       %% is_record/2,3:
3399       <<"etsc(fun(E) ->
3400                Q = qlc:q([element(1, X) || X <- ets:table(E),
3401                                            erlang:is_record(X, r, 2)]),
3402                 [r] = qlc:e(Q),
3403                 [r] = lookup_keys(Q)
3404         end, [{keypos,1}], [#r{}])">>,
3405       <<"etsc(fun(E) ->
3406                Q = qlc:q([element(1, X) || X <- ets:table(E),
3407                                            is_record(X, r, 2)]),
3408                 [r] = qlc:e(Q),
3409                 [r] = lookup_keys(Q)
3410         end, [{keypos,1}], [#r{}])">>,
3411       {cres,
3412        <<"etsc(fun(E) ->
3413                Q = qlc:q([element(1, X) || X <- ets:table(E),
3414                                            record(X, r)]),
3415                 [r] = qlc:e(Q),
3416                 [r] = lookup_keys(Q)
3417         end, [{keypos,1}], [#r{}])">>,
3418        {warnings,[{{4,45},erl_lint,{obsolete_guard,{record,2}}}]}},
3419       <<"etsc(fun(E) ->
3420                Q = qlc:q([element(1, X) || X <- ets:table(E),
3421                                            erlang:is_record(X, r)]),
3422                 [r] = qlc:e(Q),
3423                 [r] = lookup_keys(Q)
3424         end, [{keypos,1}], [#r{}])">>,
3425       <<"etsc(fun(E) ->
3426                Q = qlc:q([element(1, X) || X <- ets:table(E),
3427                                            is_record(X, r)]),
3428                 [r] = qlc:e(Q),
3429                 [r] = lookup_keys(Q)
3430         end, [{keypos,1}], [#r{}])">>
3431
3432       ],
3433
3434    ok = run(Config, <<"-record(r, {a}).\n">>, TsR),
3435
3436    Ts2 = [
3437       <<"etsc(fun(E) ->
3438                 Q0 = qlc:q([X ||
3439                                X <- ets:table(E),
3440                                (element(1, X) =:= 1) or
3441                                  (element(1, X) =:= 2)],
3442                           {cache,ets}),
3443                 Q = qlc:q([{X,Y} ||
3444                               X <- [1,2],
3445                               Y <- Q0]),
3446                 {qlc,_,[{generate,_,{list,[1,2]}},
3447                         {generate,_,{table,_}}], []} = i(Q),
3448                 [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = lists:sort(qlc:e(Q)),
3449                 [1,2] = lookup_keys(Q)
3450          end, [{keypos,1}], [{1},{2}])">>,
3451
3452       <<"etsc(fun(E) ->
3453                 Q0 = qlc:q([X ||
3454                                X <- ets:table(E),
3455                                (element(1, X) =:= 1) or
3456                                  (element(1, X) =:= 2)]),
3457                 Q = qlc:q([{X,Y} ||
3458                               X <- [1,2],
3459                               Y <- Q0],
3460                           {cache,true}),
3461                 {qlc,_,[{generate,_,{list,[1,2]}},
3462                         {generate,_,{table,_}}],[]} = i(Q),
3463                 [1,2] = lookup_keys(Q)
3464          end, [{keypos,1}], [{1},{2}])">>,
3465
3466       %% One introduced QLC expression (join, ms), and the cache option.
3467       <<"%% Match spec and lookup. The lookup is done twice, which might
3468          %% be confusing...
3469          etsc(fun(E) ->
3470                       Q = qlc:q([{X,Y} ||
3471                                     X <- [1,2],
3472                                     {Y} <- ets:table(E),
3473                                     (Y =:= 1) or (Y =:= 2)],
3474                                 []),
3475                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3476                       {qlc,_,[{generate,_,{list,[1,2]}},
3477                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3478                       [1,2] = lookup_keys(Q)
3479               end, [{keypos,1}], [{1},{2},{3}])">>,
3480       <<"%% The same as last example, but with cache.
3481          %% No cache needed (always one lookup only).
3482          etsc(fun(E) ->
3483                       Q = qlc:q([{X,Y} ||
3484                                     X <- [1,2],
3485                                     {Y} <- ets:table(E),
3486                                     (Y =:= 1) or (Y =:= 2)],
3487                                 [cache]),
3488                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3489                       {qlc,_,[{generate,_,{list,[1,2]}},
3490                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3491                       [1,2] = lookup_keys(Q)
3492               end, [{keypos,1}], [{1},{2},{3}])">>,
3493
3494       <<"%% And again, this time only lookup, no mach spec.
3495          etsc(fun(E) ->
3496                       Q = qlc:q([{X,Y} ||
3497                                     X <- [1,2],
3498                                     Y <- ets:table(E),
3499                                     (element(1, Y) =:= 1)
3500                                      or (element(1, Y) =:= 2)],
3501                                 []),
3502                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3503                       {qlc,_,[{generate,_,{list,[1,2]}},
3504                               {generate,_,{table,_}}],[]} = i(Q),
3505                       [1,2] = lookup_keys(Q)
3506               end, [{keypos,1}], [{1},{2},{3}])">>,
3507       <<"%% As last one, but with cache.
3508          %% No cache needed (always one lookup only).
3509          etsc(fun(E) ->
3510                       Q = qlc:q([{X,Y} ||
3511                                     X <- [1,2],
3512                                     Y <- ets:table(E),
3513                                     (element(1, Y) =:= 1)
3514                                      or (element(1, Y) =:= 2)],
3515                                 [cache]),
3516                       {qlc,_,[{generate,_,{list,[1,2]}},
3517                               {generate,_,{table,_}}],[]} = i(Q),
3518                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3519                       [1,2] = lookup_keys(Q)
3520               end, [{keypos,1}], [{1},{2},{3}])">>,
3521
3522       <<"%% Lookup only. No cache.
3523          etsc(fun(E) ->
3524                       Q = qlc:q([{X,Y} ||
3525                                     X <- [1,2],
3526                                     {Y=2} <- ets:table(E)],
3527                                 []),
3528                       {qlc,_,[{generate,_,{list,[1,2]}},
3529                               {generate,_,{table,_}}],[]} = i(Q),
3530                       [{1,2},{2,2}] = qlc:e(Q),
3531                       [2] = lookup_keys(Q)
3532               end, [{keypos,1}], [{1},{2},{3}])">>,
3533       <<"%% Lookup only. No cache.
3534          etsc(fun(E) ->
3535                       Q = qlc:q([{X,Y} ||
3536                                     X <- [1,2],
3537                                     {Y=2} <- ets:table(E)],
3538                                 [cache]),
3539                       {qlc,_,[{generate,_,{list,[1,2]}},
3540                               {generate,_,{table,_}}],[]} = i(Q),
3541                       [{1,2},{2,2}] = qlc:e(Q),
3542                       [2] = lookup_keys(Q)
3543               end, [{keypos,1}], [{1},{2},{3}])">>,
3544       <<"%% Matchspec only. No cache.
3545          etsc(fun(E) ->
3546                       Q = qlc:q([{X,Y} ||
3547                                     X <- [1,2],
3548                                     {Y} <- ets:table(E),
3549                                     Y > 1],
3550                                 []),
3551                       {qlc,_,[{generate,_,{list,[1,2]}},
3552                               {generate,_,
3553                                {table,{ets,_,[_,[{traverse,_}]]}}}],[]} =
3554                                       i(Q),
3555                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3556                       false = lookup_keys(Q)
3557               end, [{keypos,1}], [{1},{2},{3}])">>,
3558       <<"%% Matchspec only. Cache
3559          etsc(fun(E) ->
3560                       Q = qlc:q([{X,Y} ||
3561                                     X <- [1,2],
3562                                     {Y} <- ets:table(E),
3563                                     Y > 1],
3564                                 [cache]),
3565                       {qlc,_,[{generate,_,{list,[1,2]}},
3566                            {generate,_,{qlc,_,
3567                           [{generate,_,{table,{ets,_,[_,[{traverse,_}]]}}}],
3568                          [{cache,ets}]}}],[]} = i(Q),
3569                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3570                       false = lookup_keys(Q)
3571               end, [{keypos,1}], [{1},{2},{3}])">>,
3572       <<"%% An empty list. Always unique and cached.
3573          Q = qlc:q([X || {X} <- [], X =:= 1, begin X > 0 end],
3574                   [{cache,true},{unique,true}]),
3575          {qlc,_,[{generate,_,{list,[]}},_],[{unique,true}]} = i(Q),
3576          _ = qlc:info(Q),
3577          [] = qlc:e(Q)">>,
3578       <<"%% A list is always cached.
3579          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2]],
3580                    [cache]),
3581          {qlc,_,[{generate,_,{list,[1,2]}},
3582                  {generate,_,{list,[2,1,2]}}],[]} = i(Q),
3583          [{2,1},{1,1},{2,1},{2,2},{1,2},{2,2}] = qlc:e(Q)">>,
3584       <<"%% But a processed list is never cached.
3585          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2], X > 1],
3586                    [cache]),
3587          {qlc,_,[{generate,_, {list,[1,2]}},
3588                  {generate,_,{qlc,_,
3589                               [{generate,_,{list,{list,[2,1,2]},_}}],
3590                               [{cache,ets}]}}],[]} = i(Q),
3591          [{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>,
3592       <<"%% A bug fixed in R11B-2: coalescing simple_qlc:s works now.
3593          Q0 = qlc:q([X || {X} <- [{1},{2},{3}]],  {cache, ets}),
3594          Q1 = qlc:q([X || X <- Q0], {cache, list}),
3595          Q = qlc:q([{Y,X} || Y <- [1,2], X <- Q1, X < 2], {cache, list}),
3596          {qlc,_,[{generate,_,{list,_}},
3597                  {generate,_,{qlc,_,[{generate,_,{list,{list,_},_}}],
3598                               [{cache,ets}]}},_],[]} = i(Q),
3599          [{1,1},{2,1}] = qlc:e(Q)">>,
3600       <<"Q = qlc:q([{X,Y} || Y <- [1,2], X <- [1,2], X > 1],
3601                    [cache,unique]),
3602          {qlc,_,[{generate,_,{list,[1,2]}},
3603                  {generate,_,{qlc,_,
3604                               [{generate,_,{list,{list,[1,2]},_}}],
3605                               [{cache,ets},{unique,true}]}}],
3606           [{unique,true}]} = i(Q),
3607          [{2,1},{2,2}] = qlc:e(Q)">>,
3608       <<"L = [1,2,3],
3609          QH1 = qlc:q([{X} || X <- L, X > 1]),
3610          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache]),
3611          [{{2}},{{3}}] = qlc:e(QH2),
3612          {list,{list,{list,L},_},_} = i(QH2)">>,
3613       <<"L = [1,2,3,1,2,3],
3614          QH1 = qlc:q([{X} || X <- L, X > 1]),
3615          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache,unique]),
3616          [{{2}},{{3}}] = qlc:e(QH2),
3617          {qlc,_,[{generate,_,{list,{list,{list,L},_},_}}],
3618           [{unique,true}]} = i(QH2)">>
3619
3620      ],
3621
3622    ok = run(Config, Ts2),
3623
3624    LTs = [
3625       <<"etsc(fun(E) ->
3626                       Q  = qlc:q([X || X <- ets:table(E),
3627                                        element(1, X) =:= 1],
3628                                  {lookup,true}),
3629                       {table,L} = i(Q),
3630                       true = is_list(L),
3631                       [{1,a}] = qlc:e(Q),
3632                       [1] = lookup_keys(Q)
3633               end, [{1,a},{2,b}])">>,
3634       <<"%% No lookup, use the match spec for traversal instead.
3635          etsc(fun(E) ->
3636                       Q  = qlc:q([X || X <- ets:table(E),
3637                                        element(1, X) =:= 1],
3638                                  {lookup,false}),
3639                       {table,{ets,table,_}} = i(Q),
3640                       [{1,a}] = qlc:e(Q),
3641                       false = lookup_keys(Q)
3642               end, [{1,a},{2,b}])">>,
3643       <<"%% As last one. {max_lookup,0} has the same effect.
3644          etsc(fun(E) ->
3645                       Q  = qlc:q([X || X <- ets:table(E),
3646                                        element(1, X) =:= 1],
3647                                  {max_lookup,0}),
3648                       {table,{ets,table,_}} = i(Q),
3649                       [{1,a}] = qlc:e(Q),
3650                       false = lookup_keys(Q)
3651               end, [{1,a},{2,b}])">>
3652
3653       ],
3654
3655    ok = run(Config, LTs),
3656
3657    ok.
3658
3659%% Lookup keys. With records.
3660lookup_rec(Config) when is_list(Config) ->
3661    Ts = [
3662       <<"etsc(fun(E) ->
3663                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3664                                (A =:= 3) or (4 =:= A)]),
3665                [3] = qlc:e(Q),
3666                [3,4] = lookup_keys(Q)
3667            end, [{keypos,2}], [#r{a = a}, #r{a = 3}, #r{a = 5}])">>,
3668
3669       {cres,
3670        <<"etsc(fun(E) ->
3671                 Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3672                                 (A =:= 3) or (4 =:= A)]),
3673                 [] = qlc:e(Q),
3674                 false = lookup_keys(Q)
3675             end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3676        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3677        []},
3678
3679      <<"%% Compares an integer and a float.
3680         etsc(fun(E) ->
3681                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3682                                (A == 17) or (17.0 == A)]),
3683                [_] = qlc:e(Q),
3684                [_] = lookup_keys(Q)
3685            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3686
3687      <<"%% Compares an integer and a float.
3688         %% There is a test in qlc_pt.erl (Op =:= '=:=', C1 =:= C2), but
3689         %% that case is handled in an earlier clause (unify ... E, E).
3690         etsc(fun(E) ->
3691                Q = qlc:q([A || #r{a = 17.0 = A} <- ets:table(E),
3692                                (A =:= 17) or (17.0 =:= A)]),
3693                [_] = qlc:e(Q),
3694                [_] = lookup_keys(Q)
3695            end, [{keypos,2}], [#r{a = 17.0}, #r{a = 3}, #r{a = 5}])">>,
3696
3697      <<"%% Matches an integer and a float.
3698         etsc(fun(E) ->
3699                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3700                                (A =:= 17) or (17.0 =:= A)]),
3701                [_] = qlc:e(Q),
3702                [_] = lookup_keys(Q)
3703            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3704
3705      <<"etsc(fun(E) ->
3706                F = fun(_) -> 17 end,
3707                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3708                                (F(A) =:= 3) and (A =:= 4)]),
3709                [] = qlc:e(Q),
3710                false = lookup_keys(Q) % F(A) could fail
3711            end, [{keypos,2}], [#r{a = 4}, #r{a = 3}, #r{a = 5}])">>,
3712
3713      <<"etsc(fun(E) ->
3714                Q = qlc:q([X || {X} <- ets:table(E),
3715                                #r{} == X]),
3716                [#r{}] = lists:sort(qlc:e(Q)),
3717                {call,_,_,[_,_]} = i(Q, {format, abstract_code}),
3718                [#r{}] = lookup_keys(Q)
3719        end, [{#r{}},{#r{a=foo}}])">>,
3720
3721      <<"etsc(fun(E) ->
3722                Q = qlc:q([R#r.a || R <- ets:table(E), R#r.a =:= foo]),
3723                [foo] = qlc:e(Q),
3724                [_] = lookup_keys(Q)
3725        end, [{keypos,2}], [#r{a=foo}])">>
3726       ],
3727    run(Config, <<"-record(r, {a}).\n">>, Ts),
3728    ok.
3729
3730%% Using indices for lookup.
3731indices(Config) when is_list(Config) ->
3732    Ts = [
3733       <<"L = [{1,a},{2,b},{3,c}],
3734          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3735                                       (element(2, X) =:= a)
3736                                           or (b =:= element(2, X))]),
3737          {list, {table,{qlc_SUITE,list_keys,[[a,b],2,L]}}, _MS} = i(QH),
3738          [1,2] = qlc:eval(QH)">>,
3739
3740       <<"L = [{1,a},{2,b},{3,c}],
3741          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3742                                       begin (element(2, X) =:= a)
3743                                           or (b =:= element(2, X)) end]),
3744          {qlc,_,[{generate,_,{table,{call,_,
3745                               {remote,_,_,{atom,_,the_list}},_}}},_],[]}
3746                  = i(QH),
3747          [1,2] = qlc:eval(QH)">>,
3748
3749       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3750          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2,3]),
3751                                       (element(3, X) =:= q)
3752                                           or (r =:= element(3, X))]),
3753          {list, {table,{qlc_SUITE,list_keys, [[q,r],3,L]}}, _MS} = i(QH),
3754          [1,2] = qlc:eval(QH)">>,
3755
3756       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3757          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, 1, [2]),
3758                                       (element(3, X) =:= q)
3759                                           or (r =:= element(3, X))]),
3760          {qlc,_,[{generate,_,{table,{call,_,_,_}}},
3761                  _],[]} = i(QH),
3762          [1,2] = qlc:eval(QH)">>,
3763
3764       <<"L = [{a,1},{b,2},{c,3}],
3765          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3766                           ((K =:= a) or (K =:= b) or (K =:= c))
3767                               and ((I =:= 1) or (I =:= 2))],
3768                     {max_lookup, 3}),
3769          {list, {table,{qlc_SUITE,list_keys,[[a,b,c],1,L]}}, _MS} = i(QH),
3770          [{a,1},{b,2}] = qlc:eval(QH)">>,
3771
3772       <<"L = [{a,1},{b,2},{c,3}],
3773          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3774                           ((K =:= a) or (K =:= b) or (K =:= c))
3775                               and ((I =:= 1) or (I =:= 2))],
3776                     {max_lookup, 2}),
3777          {list, {table,{qlc_SUITE,list_keys, [[1,2],2,L]}}, _MS} = i(QH),
3778          [{a,1},{b,2}] = qlc:eval(QH)">>,
3779
3780       <<"L = [{a,1,x,u},{b,2,y,v},{c,3,z,w}],
3781          QH = qlc:q([E || {K,I1,I2,I3}=E <- qlc_SUITE:table(L, 1, [2,3,4]),
3782                           ((K =/= a) or (K =/= b) or (K =/= c))
3783                             and ((I1 =:= 1) or (I1 =:= 2) or
3784                                  (I1 =:= 3) or (I1 =:= 4))
3785                             and ((I2 =:= x) or (I2 =:= z))
3786                             and ((I3 =:= v) or (I3 =:= w))],
3787                     {max_lookup, 5}),
3788          {list, {table,{qlc_SUITE,list_keys, [[x,z],3,L]}}, _MS} = i(QH),
3789          [{c,3,z,w}] = qlc:eval(QH)">>
3790
3791       ],
3792    run(Config, <<"-record(r, {a}).\n">>, Ts),
3793    ok.
3794
3795%% Test the table/2 callback functions parent_fun and stop_fun.
3796pre_fun(Config) when is_list(Config) ->
3797    Ts = [
3798       <<"PF = process_flag(trap_exit, true),
3799          %% cursor: table killing parent
3800          L = [{1,a},{2,b},{3,c}],
3801          F1 = fun() ->
3802                   QH = qlc:q([element(1, X) ||
3803                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3804                                (element(2, X) =:= a)
3805                                    or (b =:= element(2, X))]),
3806                   _ = qlc:info(QH),
3807                   _ = qlc:cursor(QH)
3808               end,
3809          Pid1 = spawn_link(F1),
3810          receive {'EXIT', Pid1, killed} ->
3811              ok
3812          end,
3813          timer:sleep(1),
3814          process_flag(trap_exit, PF)">>,
3815
3816       <<"PF = process_flag(trap_exit, true),
3817          %% eval without cursor: table killing parent
3818          L = [{1,a},{2,b},{3,c}],
3819          F2 = fun() ->
3820                 QH = qlc:q([element(1, X) ||
3821                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3822                                (element(2, X) =:= a)
3823                                    or (b =:= element(2, X))]),
3824                 _ = qlc:eval(QH)
3825               end,
3826          Pid2 = spawn_link(F2),
3827          receive {'EXIT', Pid2, killed} ->
3828              ok
3829          end,
3830          process_flag(trap_exit, PF)">>,
3831
3832       <<"L = [{1,a},{2,b},{3,c}],
3833          QH = qlc:q([element(1, X) ||
3834                        X <- qlc_SUITE:table_parent_throws(L, [2]),
3835                        (element(2, X) =:= a)
3836                            or (b =:= element(2, X))]),
3837          _ = qlc:info(QH),
3838          {throw,thrown} = (catch {any_term,qlc:cursor(QH)}),
3839          {throw,thrown} = (catch {any_term,qlc:eval(QH)})">>,
3840
3841       <<"L = [{1,a},{2,b},{3,c}],
3842          QH = qlc:q([element(1, X) ||
3843                        X <- qlc_SUITE:table_parent_exits(L, [2]),
3844                        (element(2, X) =:= a)
3845                            or (b =:= element(2, X))]),
3846          _ = qlc:info(QH),
3847          {'EXIT', {badarith,_}} = (catch qlc:cursor(QH)),
3848          {'EXIT', {badarith,_}} = (catch qlc:eval(QH))">>,
3849
3850       <<"L = [{1,a},{2,b},{3,c}],
3851          QH = qlc:q([element(1, X) ||
3852                        X <- qlc_SUITE:table_bad_parent_fun(L, [2]),
3853                        (element(2, X) =:= a)
3854                            or (b =:= element(2, X))]),
3855          {'EXIT', {badarg,_}} = (catch qlc:cursor(QH)),
3856          {'EXIT', {badarg,_}} = (catch qlc:eval(QH))">>,
3857
3858       <<"%% Very simple test of stop_fun.
3859          Ets = ets:new(apa, [public]),
3860          L = [{1,a},{2,b},{3,c}],
3861          H = qlc:q([X || {X,_} <- qlc_SUITE:stop_list(L, Ets)]),
3862          C = qlc:cursor(H),
3863          [{stop_fun,StopFun}] = ets:lookup(Ets, stop_fun),
3864          StopFun(),
3865          {'EXIT', {{qlc_cursor_pid_no_longer_exists, _}, _}} =
3866                  (catch qlc:next_answers(C, all_remaining)),
3867          ets:delete(Ets)">>
3868
3869       ],
3870
3871    run(Config, Ts),
3872    ok.
3873
3874%% Lookup keys. With records.
3875skip_filters(Config) when is_list(Config) ->
3876    %% Skipped filters
3877    TsS = [
3878       %% Cannot skip the filter.
3879       <<"etsc(fun(E) ->
3880                H = qlc:q([X || X <- ets:table(E),
3881                          (element(1, X) =:= 1) xor (element(1, X) =:= 1)]),
3882                [] = qlc:eval(H),
3883                [1] = lookup_keys(H)
3884               end, [{keypos,1}], [{1},{2}])">>,
3885
3886       %% The filter can be skipped. Just a lookup remains.
3887       <<"etsc(fun(E) ->
3888                H = qlc:q([X || X <- ets:table(E),
3889                          (element(1, X) =:= 1) or (element(1, X) =:= 1)]),
3890                [{1}] = qlc:eval(H),
3891                {table, _} = i(H),
3892                [1] = lookup_keys(H)
3893               end, [{keypos,1}], [{1},{2}])">>,
3894
3895       %% safe_unify fails on 3 and <<X:32>>
3896       <<"etsc(fun(E) ->
3897                H = qlc:q([X || X <- ets:table(E),
3898                     (element(1, X) =:= 1) and (3 =:= <<X:32>>)]),
3899                [] = qlc:eval(H),
3900                [1] = lookup_keys(H)
3901               end, [{keypos,1}], [{1},{2}])">>,
3902
3903       %% Two filters are skipped.
3904       <<"etsc(fun(E) ->
3905                Q = qlc:q([{B,C,D} || {A={C},B} <- ets:table(E),
3906                                      (A =:= {1}) or (A =:= {2}),
3907                                      (C =:= 1) or (C =:= 2),
3908                                      D <- [1,2]]),
3909                {qlc,_,[{generate,_,{table,_}},{generate,_,{list,[1,2]}}],[]}
3910                  = i(Q),
3911                [{1,1,1},{1,1,2},{2,2,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
3912                [{1},{2}] = lookup_keys(Q)
3913         end, [{{1},1},{{2},2},{{3},3}])">>,
3914
3915       <<"etsc(fun(E) ->
3916                Q = qlc:q([{B,C} || {A={C},B} <- ets:table(E),
3917                                    (A =:= {1}) or (A =:= {2}),
3918                                    (C =:= 1) or (C =:= 2)]),
3919                {qlc,_,[{generate,_,{table,_}}],[]} = i(Q),
3920                [{1,1},{2,2}] = lists:sort(qlc:eval(Q)),
3921                [{1},{2}] = lookup_keys(Q)
3922         end, [{{1},1},{{2},2},{{3},3}])">>,
3923
3924       %% Lookup. No match spec, no filter.
3925       <<"etsc(fun(E) ->
3926                Q = qlc:q([X || X <- ets:table(E),
3927                               element(1, X) =:= 1]),
3928                {table, _} = i(Q),
3929                [{1}] = qlc:e(Q),
3930                [1] = lookup_keys(Q)
3931         end, [{1},{2}])">>,
3932
3933       <<"etsc(fun(E) ->
3934                 Q = qlc:q([{X,Y} || X <- ets:table(E),
3935                                     element(1, X) =:= 1,
3936                                     Y <- [1,2]]),
3937                 {qlc,_,[{generate,_,{table,_}},{generate,_,{list,_}}],[]}
3938                      = i(Q),
3939                 [{{1},1},{{1},2}] = lists:sort(qlc:e(Q)),
3940                 [1] = lookup_keys(Q)
3941         end, [{1},{2}])">>,
3942
3943       <<"etsc(fun(E) ->
3944                 Q = qlc:q([X || {X,Y} <- ets:table(E),
3945                                 X =:= a,
3946                                 X =:= Y]),
3947                 {list,{table,_},_} = i(Q),
3948                 [a] = qlc:e(Q),
3949                 [a] = lookup_keys(Q)
3950          end, [{a,a},{b,c},{c,a}])">>,
3951
3952       %% The imported variable (A) is never looked up in the current
3953       %% implementation. This means that the first filter cannot be skipped;
3954       %% the constant 'a' is looked up, and then the first filter evaluates
3955       %% to false.
3956       <<"etsc(fun(E) ->
3957                 A = 3,
3958                 Q = qlc:q([X || X <- ets:table(E),
3959                                 A == element(1,X),
3960                                 element(1,X) =:= a]),
3961                 [] = qlc:e(Q),
3962                 [a] = lookup_keys(Q)
3963          end, [{a},{b},{c}])">>,
3964
3965       %% No lookup.
3966       {cres,
3967        <<"etsc(fun(E) ->
3968                  Q = qlc:q([X || {X} <- ets:table(E),
3969                                  X =:= 1,
3970                                  X =:= 2]),
3971                  {table, _} = i(Q),
3972                  [] = qlc:e(Q),
3973                  false = lookup_keys(Q)
3974          end, [{1,1},{2,0}])">>,
3975        %% {warnings,[{{4,37},qlc,nomatch_filter}]}},
3976        []},
3977
3978       <<"etsc(fun(E) ->
3979                 Q = qlc:q([{A,B,C} ||
3980                               {A} <- ets:table(E),
3981                               A =:= 1,
3982                               {B} <- ets:table(E),
3983                               B =:= 2,
3984                               {C} <- ets:table(E),
3985                               C =:= 3]),
3986                 {qlc,_,[{generate,_,{list,{table,_},_}},
3987                         {generate,_,{list,{table,_},_}},
3988                         {generate,_,{list,{table,_},_}}],[]} = i(Q),
3989                 [{1,2,3}] = qlc:e(Q),
3990                 [1,2,3] = lookup_keys(Q)
3991          end, [{0},{1},{2},{3},{4}])">>
3992
3993           ],
3994    run(Config, TsS),
3995
3996    Ts = [
3997       <<"etsc(fun(E) ->
3998                 H = qlc:q([X || {X,_} <- ets:table(E),
3999                                 X =:= 2]),
4000                 {list,{table,_},_} = i(H),
4001                 [2] = qlc:e(H)
4002         end, [{1,a},{2,b}])">>,
4003
4004       <<"etsc(fun(E) ->
4005                 H = qlc:q([X || {X,_} <- ets:table(E),
4006                                 ((X =:= 2) or (X =:= 1)) and (X > 1)]),
4007                 {list,{table,_},_} = i(H),
4008                 [2] = qlc:e(H)
4009         end, [{1,a},{2,b}])">>,
4010
4011       <<"etsc(fun(E) ->
4012                 H = qlc:q([X || {X,Y} <- ets:table(E),
4013                                 (X =:= 2) and (Y =:= b)]),
4014                 {list,{table,_},_} = i(H),
4015                 [2] = qlc:e(H)
4016         end, [{1,a},{2,b}])">>,
4017
4018       <<"etsc(fun(E) ->
4019                 H = qlc:q([X || X <- ets:table(E),
4020                                 (element(1,X) =:= 2) and (X =:= {2,b})]),
4021                 {list,{table,_},_} = i(H),
4022                 [{2,b}] = qlc:e(H)
4023         end, [{1,a},{2,b}])">>,
4024
4025       <<"etsc(fun(E) ->
4026                 H = qlc:q([{X,Y,Z,W} ||
4027                               {X,Y} <- ets:table(E),
4028                               {Z,W} <- ets:table(E),
4029                               (Y =:= 3) or (Y =:= 4)]),
4030                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4031                         {generate,_,{table,{ets,table,_}}}],[]} = i(H),
4032                 [{a,3,a,3},{a,3,b,5}] = lists:sort(qlc:e(H))
4033         end, [{a,3},{b,5}])">>,
4034
4035       <<"etsc(fun(E) ->
4036                 H = qlc:q([{X,Y} ||
4037                               {X,Y=3} <- ets:table(E), % no matchspec
4038                               %% Two columns restricted, but lookup anyway
4039                               (X =:= a)]),
4040                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4041                 [{a,3}] = qlc:e(H)
4042         end, [{a,3},{b,4}])">>,
4043
4044       <<"etsc(fun(E) ->
4045                 V = 3,
4046                 H = qlc:q([{X,Y} ||
4047                               {X,Y} <- ets:table(E),
4048                               (Y =:= V)]), % imported variable, no lookup
4049                 {table,{ets,table,_}} = i(H),
4050                 [{a,3}] = qlc:e(H)
4051         end, [{a,3},{b,4}])">>,
4052
4053       <<"etsc(fun(E) ->
4054                 V = b,
4055                 H = qlc:q([{X,Y} ||
4056                               {X,Y} <- ets:table(E),
4057                               (X =:= V)]), % imported variable, lookup
4058                 {list,{table,_},_} = i(H),
4059                 [{b,4}] = qlc:e(H)
4060         end, [{a,3},{b,4}])">>,
4061
4062       <<"H = qlc:q([{A,B} || {{A,B}} <- [{{1,a}},{{2,b}}],
4063                              A =:= 1,
4064                              B =:= a]),
4065              {list,{list,[_,_]},_} = i(H),
4066              [{1,a}] = qlc:e(H)">>,
4067
4068       <<"etsc(fun(E) ->
4069                 H = qlc:q([{A,B} || {{A,B}} <- ets:table(E),
4070                                     A =:= 1,
4071                                     B =:= a]),
4072                 {list,{table,_},_} = i(H),
4073                 [{1,a}] = qlc:e(H)
4074         end, [{{1,a}},{{2,b}}])">>,
4075
4076       %% The filters are skipped, and the guards of the match specifications
4077       %% are skipped as well. Only the transformations of the matchspecs
4078       %% are kept.
4079       <<"etsc(fun(E1) ->
4080                 etsc(fun(E2) ->
4081                              H = qlc:q([{X,Y,Z,W} ||
4082                                             {X,_}=Z <- ets:table(E1),
4083                                             W={Y} <- ets:table(E2),
4084                                             (X =:= 1) or (X =:= 2),
4085                                             (Y =:= a) or (Y =:= b)]
4086                                         ,{lookup,true}
4087                                        ),
4088                              {qlc,_,[{generate,_,{list,{table,_},
4089                                                   [{{'$1','_'},[],['$_']}]}},
4090                                      {generate,_,{list,{table,_},
4091                                                   [{{'$1'},[],['$_']}]}}],[]}
4092                              = i(H),
4093                              [{1,a,{1,a},{a}},
4094                               {1,b,{1,a},{b}},
4095                               {2,a,{2,b},{a}},
4096                               {2,b,{2,b},{b}}] = qlc:e(H)
4097                      end, [{a},{b}])
4098         end, [{1,a},{2,b}])">>,
4099
4100       %% The same example again, but this time no match specs are run.
4101       <<"fun(Z) ->
4102              etsc(fun(E1) ->
4103                     etsc(fun(E2) ->
4104                                  H = qlc:q([{X,Y} ||
4105                                                 Z > 2,
4106                                                 X <- ets:table(E1),
4107                                                 Y <- ets:table(E2),
4108                                                 (element(1, X) =:= 1) or
4109                                                 (element(1, X) =:= 2),
4110                                                 (element(1, Y) =:= a) or
4111                                                 (element(1, Y) =:= b)]
4112                                             ,{lookup,true}
4113                                            ),
4114                                  {qlc,_,[_,{generate,_,{table,_}},
4115                                          {generate,_,{table,_}}],[]} = i(H),
4116                                  [{{1,a},{a}},
4117                                   {{1,a},{b}},
4118                                   {{2,b},{a}},
4119                                   {{2,b},{b}}] = qlc:e(H)
4120                          end, [{a},{b}])
4121             end, [{1,a},{2,b}])
4122         end(4)">>,
4123
4124       %% Once again, this time with a join.
4125       <<"etsc(fun(E1) ->
4126                 etsc(fun(E2) ->
4127                              H = qlc:q([{X,Y,Z,W} ||
4128                                             {X,V}=Z <- ets:table(E1),
4129                                             W={Y} <- ets:table(E2),
4130                                             (X =:= 1) or (X =:= 2),
4131                                             (Y =:= a) or (Y =:= b),
4132                                             Y =:= V]
4133                                         ,[{lookup,true},{join,merge}]
4134                                        ),
4135                              {qlc,_,[{generate,_,{qlc,_,
4136                                [{generate,_,{qlc,_,[{generate,_,
4137                                    {keysort,{list,{table,_},_},2,[]}},
4138                                 _C1,_C2],[]}},
4139                                  {generate,_,
4140                                      {qlc,_,[{generate, _,
4141                                         {keysort,{list,{table,_},_},1,[]}},
4142                                              _C3],
4143                                       []}},
4144                                 _],
4145                                [{join,merge}]}},_],[]} = i(H),
4146                              [{1,a,{1,a},{a}},{2,b,{2,b},{b}}] =
4147                                  lists:sort(qlc:e(H))
4148                      end, [{a},{b}])
4149         end, [{1,a},{2,b}])">>,
4150
4151       %% Filters 2 and 3 are not skipped.
4152       %% (Only one filter at a time is tried by the parse transform.)
4153       <<"etsc(fun(E) ->
4154                 H = qlc:q([X || {{A,B}=X,Y} <- ets:table(E), % no matchspec
4155                                     Y =:= 3,
4156                                     A =:= 1,
4157                                     B =:= a]),
4158
4159                 {qlc,_,[{generate,_,{table,_}},_,_,_],[]}= i(H),
4160                 [{1,a}] = qlc:e(H)
4161         end, [{{1,a},3},{{2,b},4}])">>,
4162
4163       <<"etsc(fun(E) ->
4164                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4165                                  (X =:= 3) and (X > 3)]),
4166                 {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4167                 [] = qlc:e(H)
4168         end, [{3,a},{4,b}])">>,
4169
4170       <<"etsc(fun(E) ->
4171                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4172                                 (X =:= 3) or true]),
4173                 {qlc,_,[{generate,_,{table,{ets,table,_}}},_],[]} = i(H),
4174                 [3,4] = lists:sort(qlc:e(H))
4175         end, [{3,a},{4,b}])">>,
4176
4177       <<"etsc(fun(E) ->
4178                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4179                                 (X =:= 3) or false]),
4180                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4181                 [3] = lists:sort(qlc:e(H))
4182         end, [{3,a},{4,b}])">>,
4183
4184       <<"etsc(fun(E) ->
4185                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4186                                 (X =:= X) and (X =:= 3)]),
4187                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4188                 [3] = lists:sort(qlc:e(H))
4189         end, [{3,a},{4,b}])">>,
4190
4191       %% The order of filters matters. A guard filter cannot be used
4192       %% unless there are no non-guard filter placed before the guard
4193       %% filter that uses the guard filter's generator. There is
4194       %% more examples in join_filter().
4195       <<"etsc(fun(E) ->
4196                 %% Lookup.
4197                 Q = qlc:q([{A,B,A} ||
4198                               {A=_,B} <- ets:table(E), % no match spec
4199                               A =:= 1,
4200                               begin 1/B > 0 end]),
4201                 [{1,1,1}] = lists:sort(qlc:e(Q))
4202         end, [{1,1},{2,0}])">>,
4203       <<"etsc(fun(E) ->
4204                 %% No lookup.
4205                 Q = qlc:q([{A,B,A} ||
4206                               {A=_,B} <- ets:table(E), % no match spec
4207                               begin 1/B > 0 end,
4208                               A =:= 1]),
4209                 {'EXIT', _} = (catch qlc:e(Q))
4210         end, [{1,1},{2,0}])">>,
4211       %% The same thing, with a match specification.
4212       <<"etsc(fun(E) ->
4213                 Q = qlc:q([{A,B,A} ||
4214                               {A,B} <- ets:table(E), % match spec
4215                               A < 2,
4216                               begin 1/B > 0 end]),
4217                 [{1,1,1}] = lists:sort(qlc:e(Q))
4218         end, [{1,1},{2,0}])">>,
4219       <<"etsc(fun(E) ->
4220                 Q = qlc:q([{A,B,A} ||
4221                               {A,B} <- ets:table(E), % match spec
4222                               begin 1/B > 0 end,
4223                               A < 2]),
4224                 {'EXIT', _} = (catch qlc:e(Q))
4225         end, [{1,1},{2,0}])">>,
4226       %% More examples, this time two tables.
4227       <<"etsc(fun(E) ->
4228                 Q = qlc:q([{A,B,C,D} ||
4229                               {A,B} <- ets:table(E), % match spec
4230                               A < 2,
4231                               {C,D} <- ets:table(E),
4232                               begin 1/B > 0 end, %\"invalidates\" next filter
4233                               C =:= 1,
4234                               begin 1/D > 0 end]),
4235                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4236                         {generate,_,{table,{ets,table,_}}},
4237                         _,_,_],[]} = i(Q),
4238                 [{1,1,1,1}] = lists:sort(qlc:e(Q))
4239         end, [{1,1},{2,0}])">>,
4240       <<"etsc(fun(E) ->
4241              Q = qlc:q([{A,B,C,D} ||
4242                            {A,B} <- ets:table(E),
4243                            {C,D} <- ets:table(E),
4244                            begin 1/B > 0 end, % \"invalidates\" two filters
4245                            A < 2,
4246                            C =:= 1,
4247                            begin 1/D > 0 end]),
4248              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4249                      {generate,_,{table,{ets,table,_}}},_,_,_,_],[]} = i(Q),
4250              {'EXIT', _} = (catch qlc:e(Q))
4251         end, [{1,1},{2,0}])">>,
4252      <<"%% There are objects in the ETS table, but none passes the filter.
4253         %% F() would not be run if it did not \"invalidate\" the following
4254         %% guards.
4255         etsc(fun(E) ->
4256                      F = fun() -> [foo || A <- [0], 1/A] end,
4257                      Q1 = qlc:q([X || {X} <- ets:table(E),
4258                                       F(), % \"invalidates\" next guard
4259                                       X =:= 17]),
4260                      {'EXIT', _} = (catch qlc:e(Q1))
4261              end, [{1},{2},{3}])">>,
4262       <<"%% The last example works just like this one:
4263          etsc(fun(E) ->
4264                      F = fun() -> [foo || A <- [0], 1/A] end,
4265                      Q1 = qlc:q([X || {X} <- ets:table(E),
4266                                       F(),
4267                                       begin X =:= 17 end]),
4268                      {'EXIT', _} = (catch qlc:e(Q1))
4269              end, [{1},{2},{3}])">>
4270
4271          ],
4272    run(Config, Ts),
4273
4274    ok.
4275
4276
4277%% ets:table/1,2.
4278ets(Config) when is_list(Config) ->
4279    Ts = [
4280       <<"E = ets:new(t, [ordered_set]),
4281          true = ets:insert(E, [{1},{2}]),
4282          {'EXIT', _} =
4283              (catch qlc:e(qlc:q([X || {X} <- ets:table(E, bad_option)]))),
4284          {'EXIT', _} =
4285              (catch qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,bad})]))),
4286          All = [{'$1',[],['$1']}],
4287          TravAll = {traverse,{select,All}},
4288          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E, TravAll)])),
4289          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,select})])),
4290          [1,2] =
4291             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, first_next})])),
4292          [2,1] =
4293             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, last_prev})])),
4294          {table,{ets,table,[_,[{traverse,{select,_}},{n_objects,1}]]}} =
4295              i(qlc:q([X || {X} <- ets:table(E, {n_objects,1})])),
4296          {qlc,_,[{generate,_,{table,{ets,table,[_,{n_objects,1}]}}},_],[]} =
4297              i(qlc:q([X || {X} <- ets:table(E,{n_objects,1}),
4298                                   begin (X >= 1) or (X < 1) end])),
4299          {qlc,_,[{generate,_,{table,{ets,table,[_]}}},_],[]} =
4300              i(qlc:q([X || {X} <- ets:table(E),
4301                                   begin (X >= 1) or (X < 1) end])),
4302          ets:delete(E)">>,
4303
4304       begin
4305       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4306       [<<"E = ets:new(apa,[]),
4307           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
4308           MS =  ">>, io_lib:format("~w", [MS]), <<",
4309           Q = qlc:q([X || {X,_} <- ets:table(E, {traverse, {select, MS}}),
4310                           X =:= 1]),
4311           R = qlc:e(Q),
4312           ets:delete(E),
4313           [] = R">>]
4314       end,
4315
4316       <<"E2 = ets:new(test, [bag]),
4317          Ref = make_ref(),
4318          true = ets:insert(E2, [{Ref,Ref}]),
4319          Q2 = qlc:q([{Val1} ||
4320                         {Ref1, Val1} <- ets:table(E2),
4321                         Ref1 =:= Ref]),
4322          S = qlc:info(Q2),
4323          true = is_list(S),
4324          [{Ref}] = qlc:e(Q2),
4325          ets:delete(E2)">>
4326
4327       ],
4328
4329    run(Config, Ts),
4330    ok.
4331
4332%% dets:table/1,2.
4333dets(Config) when is_list(Config) ->
4334    dets:start(),
4335    T = t,
4336    Fname = filename(T, Config),
4337    Ts = [
4338       [<<"T = t, Fname = \"">>, Fname, <<"\",
4339           file:delete(Fname),
4340           {ok, _} = dets:open_file(T, [{file,Fname}]),
4341           ok = dets:insert(T, [{1},{2}]),
4342           {'EXIT', _} =
4343              (catch qlc:e(qlc:q([X || {X} <- dets:table(T, bad_option)]))),
4344           {'EXIT', _} =
4345              (catch qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,bad})]))),
4346           {'EXIT', _} =
4347              (catch
4348               qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,last_prev})]))),
4349           All = [{'$1',[],['$1']}],
4350           TravAll = {traverse,{select,All}},
4351           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T, TravAll)])),
4352           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,select})])),
4353           [_,_] =
4354             qlc:e(qlc:q([X || {X} <- dets:table(T, {traverse, first_next})])),
4355           {table,{dets,table,[T,[{traverse,{select,_}},{n_objects,1}]]}} =
4356               i(qlc:q([X || {X} <- dets:table(T, {n_objects,1})])),
4357           {qlc,_,[{generate,_,{table,{dets,table,[t,{n_objects,1}]}}},_],[]}=
4358               i(qlc:q([X || {X} <- dets:table(T,{n_objects,1}),
4359                             begin (X >= 1) or (X < 1) end])),
4360           {qlc,_,[{generate,_,{table,{dets,table,[_]}}},_],[]} =
4361               i(qlc:q([X || {X} <- dets:table(T),
4362                             begin (X >= 1) or (X < 1) end])),
4363           H = qlc:q([X || {X} <- dets:table(T, {n_objects, default}),
4364                           begin (X =:= 1) or (X =:= 2) or (X =:= 3) end]),
4365           [1,2] = lists:sort(qlc:e(H)),
4366           {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4367
4368           H2 = qlc:q([X || {X} <- dets:table(T), (X =:= 1) or (X =:= 2)]),
4369           [1,2] = lists:sort(qlc:e(H2)),
4370           {list,{table,_},_} = i(H2),
4371           true = binary_to_list(<<
4372            \"ets:match_spec_run(lists:flatmap(fun(V)->dets:lookup(t,V)end,\"
4373            \"[1,2]),ets:match_spec_compile([{{'$1'},[],['$1']}]))\">>)
4374                   == format_info(H2, true),
4375
4376           H3 = qlc:q([X || {X} <- dets:table(T), (X =:= 1)]),
4377           [1] = qlc:e(H3),
4378           {list,{table,_},_} = i(H3),
4379
4380           ok = dets:close(T),
4381           file:delete(\"">>, Fname, <<"\"),
4382           ok">>],
4383
4384       begin
4385       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4386       [<<"T = t, Fname = \"">>, Fname, <<"\",
4387           {ok, _} = dets:open_file(T, [{file,Fname}]),
4388           MS =  ">>, io_lib:format("~w", [MS]), <<",
4389           ok = dets:insert(T, [{1,a},{2,b},{3,c}]),
4390           Q = qlc:q([X || {X,_} <- dets:table(T, {traverse, {select, MS}}),
4391                           X =:= 1]),
4392           R = qlc:e(Q),
4393           ok = dets:close(T),
4394           file:delete(\"">>, Fname, <<"\"),
4395           [] = R">>]
4396       end,
4397
4398       [<<"T = t, Fname = \"">>, Fname, <<"\",
4399           {ok, _} = dets:open_file(T, [{file,Fname}]),
4400           Objs = [{X} || X <- lists:seq(1,10)],
4401           ok = dets:insert(T, Objs),
4402           {ok, Where} = dets:where(T, {2}),
4403           ok = dets:close(T),
4404           qlc_SUITE:crash(Fname, Where),
4405
4406           {ok, _} = dets:open_file(T, [{file,Fname}]),
4407           HT = qlc:q([X || {X} <- dets:table(T, {traverse, first_next})]),
4408           {'EXIT',{error,{{bad_object,_},_}}} = (catch qlc:e(HT)),
4409           _ = dets:close(T),
4410
4411           {ok, _} = dets:open_file(T, [{file,Fname}]),
4412           HMS = qlc:q([X || {X} <- dets:table(T, {traverse, select})]),
4413           {error,{{bad_object,_},_}} = qlc:e(HMS),
4414           _ = dets:close(T),
4415
4416           {ok, _} = dets:open_file(T, [{file,Fname}]),
4417           HLU = qlc:q([X || {X} <- dets:table(T), X =:= 2]),
4418           {error,{{bad_object,_},_}} = qlc:e(HLU),
4419           _ = dets:close(T),
4420
4421           file:delete(Fname)">>]
4422
4423       ],
4424
4425    run(Config, Ts),
4426    _ = file:delete(Fname),
4427    ok.
4428
4429
4430%% The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.
4431join_option(Config) when is_list(Config) ->
4432    Ts = [
4433       <<"Q1 = qlc:q([X || X <- [1,2,3]],{join,merge}),
4434          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q1)}),
4435          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q1)}),
4436
4437          Q2 = qlc:q([X || X <- [1,2,3], X > 1],{join,merge}),
4438          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q2)}),
4439          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q2)}),
4440
4441          Q3 = qlc:q([{X,Y} ||
4442                         {X} <- [{1},{2},{3}],
4443                         {Y} <- [{a},{b},{c}],
4444                         X =:= Y],
4445                     {join, merge}),
4446
4447          {1,0,0,2} = join_info(Q3),
4448          [] = qlc:e(Q3),
4449
4450          Q4 = qlc:q([{X,Y} ||
4451                         {X} <- [{1},{2},{3}],
4452                         {Y} <- [{a},{b},{c}],
4453                         X > Y],
4454                     {join, lookup}),
4455          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q4)}),
4456          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q4)}),
4457
4458          Q5 = qlc:q([{X,Y} ||
4459                         {X} <- [{1},{2},{3}],
4460                         {Y} <- [{3},{4},{5}],
4461                         X == Y],
4462                     {join, merge}),
4463          [{3,3}] = qlc:e(Q5),
4464
4465          Q6 = qlc:q([{X,Y} ||
4466                         {X} <- [{1},{2},{3}],
4467                         {Y} <- [{3},{4},{5}],
4468                         X == Y],
4469                     {join, lookup}),
4470          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:info(Q6)}),
4471          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:e(Q6)}),
4472
4473          Q7 = qlc:q([{X,Y} ||
4474                         {X} <- [{1},{2},{3}],
4475                         {Y} <- [{3},{4},{5}],
4476                         X == Y],
4477                     {join, nested_loop}),
4478          {0,0,1,0} = join_info(Q7),
4479          [{3,3}] = qlc:e(Q7),
4480
4481          Q8 = qlc:q([{X,Y} ||
4482                         {X} <- [{1},{2},{3}],
4483                         {Y} <- [{3},{4},{5}],
4484                         X =:= Y],
4485                     {join, nested_loop}),
4486          {0,0,1,0} = join_info(Q8),
4487          [{3,3}] = qlc:e(Q8),
4488
4489          %% Only guards are inspected...
4490          Q9 = qlc:q([{X,Y} ||
4491                         {X} <- [{1},{2},{3}],
4492                         {Y} <- [{3},{4},{5}],
4493                         begin X =:= Y end],
4494                     {join, nested_loop}),
4495          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q9)}),
4496          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q9)}),
4497
4498          Q10 = qlc:q([{X,Y} ||
4499                         {X} <- [{1},{2},{3}],
4500                         {Y} <- [{3},{4},{5}],
4501                         X < Y],
4502                     {join, nested_loop}),
4503          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q10)}),
4504          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q10)}),
4505
4506          F = fun(J) -> qlc:q([X || X <- [1,2]], {join,J}) end,
4507          {'EXIT', {no_join_to_carry_out, _}} =
4508                (catch {foo, qlc:e(F(merge))}),
4509          {'EXIT', {no_join_to_carry_out, _}} =
4510                (catch {foo, qlc:e(F(lookup))}),
4511          {'EXIT', {no_join_to_carry_out, _}} =
4512                (catch {foo, qlc:e(F(nested_loop))}),
4513          [1,2] = qlc:e(F(any)),
4514
4515          %% No join of columns in the same table.
4516          Q11 = qlc:q([{X,Y} || {a = X, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4517                      {join,merge}),
4518          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q11)),
4519          Q12 = qlc:q([{X,Y} || {X = a, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4520                      {join,merge}),
4521          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q12)),
4522          %% X and Y are \"equal\" (same constants), but must not be joined.
4523          Q13 = qlc:q([{X,Y} || {X,_Z} <- [{a,1},{a,2},{b,1},{b,2}],
4524                                {Y} <- [{a}],
4525                                (X =:= a) and (Y =:= b) or
4526                                (X =:= b) and (Y =:= a)],
4527                     {join,merge}),
4528          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q13))
4529
4530">>,
4531
4532       <<"Q1 = qlc:q([X || X <- [1,2,3]], {lookup,true}),
4533          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q1)}),
4534          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q1)}),
4535          Q2 = qlc:q([{X,Y} || X <- [1,2,3], Y <- [x,y,z]], lookup),
4536          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q2)}),
4537          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q2)}),
4538          Q3 = qlc:q([X || {X} <- [{1},{2},{3}]], {lookup,true}),
4539          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q3)}),
4540          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q3)}),
4541
4542          E1 = create_ets(1, 10),
4543          Q4 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], lookup),
4544          {match_spec, _} = strip_qlc_call(Q4),
4545          [{3,3}] = qlc:e(Q4),
4546          Q5 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,false}),
4547          {table, ets, _} = strip_qlc_call(Q5),
4548          [{3,3}] = qlc:e(Q5),
4549          Q6 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,any}),
4550          {match_spec, _} = strip_qlc_call(Q6),
4551          [{3,3}] = qlc:e(Q6),
4552          ets:delete(E1)">>
4553
4554       ],
4555    run(Config, Ts),
4556
4557    %% The 'cache' and 'unique' options of qlc/2 affects join.
4558    CUTs = [
4559       <<"L1 = [1,2],
4560          L2 = [{1,a},{2,b}],
4561          L3 = [{a,1},{b,2}],
4562          Q = qlc:q([{X,Y,Z} ||
4563                        Z <- L1,
4564                        {X,_} <- L2,
4565                        {_,Y} <- L3,
4566                        X =:= Y],
4567                    [cache, unique]),
4568          {qlc,_,
4569              [{generate,_,{list,L1}},
4570               {generate,_,{qlc,_,[{generate,_,
4571                      {qlc,_,[{generate,_,{keysort,{list,L2},1,[]}}],[]}},
4572                                {generate,_,{qlc,_,
4573                              [{generate,_,{keysort,{list,L3},2,[]}}],[]}},_],
4574                            [{join,merge},{cache,ets},{unique,true}]}},_],
4575              [{unique,true}]} = i(Q),
4576          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q)">>,
4577       <<"L1 = [1,2],
4578          L2 = [{1,a},{2,b}],
4579          L3 = [{a,1},{b,2}],
4580          Q = qlc:q([{X,Y,Z} ||
4581                        Z <- L1,
4582                        {X,_} <- L2,
4583                        {_,Y} <- L3,
4584                        X =:= Y],
4585                    []),
4586          Options = [{cache_all,ets}, unique_all],
4587          {qlc,_,[{generate,_,{qlc,_,[{generate,_,{list,L1}}],
4588                               [{unique,true}]}},
4589                  {generate,_,{qlc,_,
4590                              [{generate,_,{qlc,_,[{generate,_,
4591                                 {keysort,{qlc,_,[{generate,_,{list,L2}}],
4592                                           [{cache,ets},{unique,true}]},
4593                                          1,[]}}],[]}},
4594                               {generate,_,{qlc,_,
4595                                    [{generate,_,{keysort,
4596                                      {qlc,_,[{generate,_,{list,L3}}],
4597                                       [{cache,ets},{unique,true}]},
4598                                                  2,[]}}],[]}},_],
4599                              [{join,merge},{cache,ets},{unique,true}]}},
4600                  _],[{unique,true}]} = i(Q, Options),
4601          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q, Options)">>
4602       ],
4603    run(Config, CUTs),
4604
4605    ok.
4606
4607%% Various aspects of filters and join.
4608join_filter(Config) when is_list(Config) ->
4609    Ts = [
4610      <<"E1 = create_ets(1, 10),
4611          Q = qlc:q([X || {X,_} <- ets:table(E1),
4612                          begin A = X * X end, % ej true (?)
4613                          X >= A]),
4614          {'EXIT', _} = (catch qlc:e(Q)),
4615          ets:delete(E1)">>,
4616
4617      %% The order of filters matters. See also skip_filters().
4618      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4619         {Z,W} <- [{a,1},{c,0}],
4620         X =:= Z,
4621         begin Y/W > 0 end]),
4622         [{a,1}] = qlc:e(Q)">>,
4623      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4624         {Z,W} <- [{a,1},{c,0}],
4625         begin Y/W > 0 end,
4626         X =:= Z]),
4627         {'EXIT', _} = (catch qlc:e(Q))">>,
4628
4629      <<"etsc(fun(E1) ->
4630                   etsc(fun(E2) ->
4631                             F = fun() -> [foo || A <- [0], 1/A] end,
4632                             Q1 = qlc:q([X || {X} <- ets:table(E1),
4633                                              {Y} <- ets:table(E2),
4634                                              F(), % invalidates next filter
4635                                              X =:= Y]),
4636                              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4637                                      {generate,_,{table,{ets,table,_}}},_,_],
4638                              []} = i(Q1),
4639                             {'EXIT', _} = (catch qlc:e(Q1))
4640                        end, [{1},{2},{3}])
4641              end, [{a},{b},{c}])">>
4642
4643    ],
4644    run(Config, Ts),
4645    ok.
4646
4647%% Lookup join.
4648join_lookup(Config) when is_list(Config) ->
4649    Ts = [
4650       <<"E1 = create_ets(1, 10),
4651          E2 = create_ets(5, 15),
4652          Q = qlc:q([{X,Y} || {_,Y} <- ets:table(E2),
4653                              {X,_} <- ets:table(E1),
4654                              X =:= Y], [{join,lookup}]),
4655          {0,1,0,0} = join_info_count(Q),
4656          R = qlc:e(Q),
4657          ets:delete(E1),
4658          ets:delete(E2),
4659          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4660
4661       <<"E1 = create_ets(1, 10),
4662          E2 = create_ets(5, 15),
4663          F = fun(J) -> qlc:q([{X,Y} || {X,_} <- ets:table(E1),
4664                                        {_,Y} <- ets:table(E2),
4665                                        X =:= Y], {join, J})
4666              end,
4667          Q = F(lookup),
4668          {0,1,0,0} = join_info_count(Q),
4669          R = qlc:e(Q),
4670          ets:delete(E1),
4671          ets:delete(E2),
4672          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4673
4674       <<"etsc(fun(E1) ->
4675                  E2 = qlc_SUITE:table([{1,a},{a},{1,b},{b}], 2, []),
4676                  Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4677                                      {_,Z} <- E2,   % (2)
4678                                      (Z =:= Y) and (X =:= a)
4679                                      or
4680                                      (Z =:= Y) and (X =:= b)]),
4681                  %% Cannot look up in (1) (X is keypos). Can look up (2).
4682                  %% Lookup-join: traverse (1), look up in (2).
4683                  {0,1,0,0} = join_info_count(Q),
4684                  [{a,a},{b,a}] = qlc:e(Q)
4685               end, [{a,a},{b,a},{c,3},{d,4}])">>,
4686
4687       <<"%% The pattern {X,_} is used to filter out looked up objects.
4688          etsc(fun(E) ->
4689                       Q = qlc:q([X || {X,_} <- ets:table(E),
4690                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
4691                                       X =:= element(1, Y)]),
4692                       {0,1,0,0} = join_info_count(Q),
4693                       [1] = qlc:e(Q)
4694               end, [{1,2},{3}])">>,
4695
4696       <<"E = ets:new(e, [bag,{keypos,2}]),
4697          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4698                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4699          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4700          Q = qlc:q([Z || {_,Y}=Z <- ets:table(E),
4701                          {X} <- [{X} || X <- lists:seq(0, 10)],
4702                          X =:= Y]),
4703          {0,1,0,0} = join_info_count(Q),
4704          R = qlc:e(Q),
4705          ets:delete(E),
4706          L = lists:sort(R)">>,
4707
4708       <<"E = ets:new(e, [bag,{keypos,2}]),
4709          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4710                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4711          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4712          Q = qlc:q([Z || {X} <- [{X} || X <- lists:seq(0, 10)],
4713                          {_,Y}=Z <- ets:table(E),
4714                          X =:= Y]),
4715          {0,1,0,0} = join_info_count(Q),
4716          R = qlc:e(Q),
4717          ets:delete(E),
4718          L = lists:sort(R)">>,
4719
4720       <<"Q = qlc:q([{XX,YY} ||
4721                            {XX,X} <- [{b,1},{c,3}],
4722                            {Y,YY} <- qlc_SUITE:table_lookup_error([{1,a}]),
4723                            X =:= Y],
4724                        {join,lookup}),
4725          {error, lookup, failed} = qlc:e(Q)">>,
4726
4727       <<"E = create_ets(1, 10),
4728          Q = qlc:q([{X,Y} ||
4729                        {X,_} <- ets:table(E),
4730                        {_,Y} <- qlc_SUITE:table_error([{a,1}], 1, err),
4731                        X =:= Y]),
4732          {0,1,0,0} = join_info_count(Q),
4733          err = qlc:e(Q),
4734          ets:delete(E)">>
4735
4736          ],
4737    run(Config, Ts),
4738    ok.
4739
4740%% Merge join.
4741join_merge(Config) when is_list(Config) ->
4742    Ts = [
4743       <<"Q = qlc:q([{X,Y} || {X} <- [], {Y} <- [{1}], X =:= Y],
4744                    {join,merge}),
4745          [] = qlc:e(Q)
4746       ">>,
4747
4748       <<"Q = qlc:q([{X,Y} || {X} <- [{1}], {Y} <- [], X =:= Y],
4749                    {join,merge}),
4750          [] = qlc:e(Q)
4751       ">>,
4752
4753       <<"Q = qlc:q([{X,Y} || {X} <- [{1},{1},{1}],
4754                              {Y} <- [{1},{1},{1}], X =:= Y],
4755                    {join,merge}),
4756          9 = length(qlc:e(Q))
4757       ">>,
4758
4759       <<"%% Two merge joins possible.
4760          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4761                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4762                                  X =:= Z,
4763                                  Y =:= W]),
4764          {qlc,_,[{generate,_,
4765                   {qlc,_,
4766                    [{generate,_,
4767                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4768                     {generate,_,
4769                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4770                     _],
4771                    [{join,merge}]}},
4772                  _,_],[]} = qlc:info(Q, {format,debug}),
4773          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4774
4775       <<"%% As the last one, but comparison.
4776          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4777                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4778                                  X == Z, % skipped
4779                                  Y =:= W]),
4780          {qlc,_,[{generate,_,
4781                   {qlc,_,
4782                    [{generate,_,
4783                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4784                     {generate,_,
4785                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4786                     _],
4787                    [{join,merge}]}},
4788                  _],[]} = qlc:info(Q, {format,debug}),
4789          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4790
4791       <<"%% This is no join.
4792          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [], {Z,W} <- [],
4793                                  X =:= Y, Z =:= W]),
4794          {0,0,0,0} = join_info_count(Q)">>,
4795
4796       <<"%% Used to replace empty ETS tables with [], but that won't work.
4797          E1 = ets:new(e1, []),
4798          E2 = ets:new(e2, []),
4799          Q = qlc:q([{X,Z,W} ||
4800                        {X, Z} <- ets:table(E1),
4801                        {W, Y} <- ets:table(E2),
4802                        X =:= Y],
4803                    {join, lookup}),
4804          [] = qlc:e(Q),
4805          ets:delete(E1),
4806          ets:delete(E2)">>,
4807
4808       <<"Q = qlc:q([{X,Y} || {X} <- [{3},{1},{0}],
4809                              {Y} <- [{1},{2},{3}],
4810                              X =:= Y]),
4811          {1,0,0,2} = join_info_count(Q),
4812          [{1,1},{3,3}] = qlc:e(Q)">>,
4813
4814       <<"QH = qlc:q([{X,Y,Z,W} || {X,Y} <- [{3,c},{2,b},{1,a}],
4815                                   {Z,W} <- [{2,b},{4,d},{5,e},{3,c}],
4816                                   X =:= Z,
4817                                   Y =:= W]),
4818          {1,0,0,2} = join_info_count(QH),
4819          [{2,b,2,b},{3,c,3,c}] = qlc:e(QH)">>,
4820
4821       <<"%% QLC finds no join column at run time...
4822          QH = qlc:q([1 || X <- [{1,2,3},{4,5,6}],
4823                           Y <- [{1,2},{3,4}],
4824                           X =:= Y]),
4825          {0,0,0,0} = join_info_count(QH),
4826          [] = qlc:e(QH)">>,
4827
4828       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
4829                           Y <- [{1,2},{3,4}],
4830                           element(1, X) =:= element(2, Y)]),
4831          {1,0,0,2} = join_info_count(QH),
4832          [{4,5,6}] = qlc:e(QH)">>,
4833
4834       <<"Q = qlc:q([{A,X,Z,W} ||
4835                        A <- [a,b,c],
4836                        {X,Z} <- [{a,1},{b,4},{c,6}],
4837                        {W,Y} <- [{2,a},{3,b},{4,c}],
4838                        X =:= Y],
4839                   {cache, list}),
4840          _ = qlc:info(Q),
4841         [{a,a,1,2},{a,b,4,3},{a,c,6,4},{b,a,1,2},{b,b,4,3},
4842          {b,c,6,4},{c,a,1,2},{c,b,4,3},{c,c,6,4}] = qlc:e(Q)">>,
4843
4844       <<"Q = qlc:q([{X,Y} ||
4845                        {X,Z} <- [{a,1},{b,4},{c,6}],
4846                        {W,Y} <- [{2,a},{3,b},{4,c}],
4847                        Z > W,
4848                        X =:= Y],
4849                    {join,merge}),
4850          {qlc,_,[{generate,_,{qlc,_,
4851                              [{generate,_,
4852                                {qlc,_,[{generate,_,{keysort,_,1,[]}}],[]}},
4853                               {generate,_,
4854                                {qlc,_,[{generate,_,{keysort,_,2,[]}}],
4855                                 []}},_],[{join,merge}]}},
4856                  _,_],[]} = i(Q),
4857          [{b,b},{c,c}] = qlc:e(Q)">>,
4858
4859       <<"E1 = create_ets(1, 10),
4860          E2 = create_ets(5, 15),
4861          %% A match spec.; Q does not see Q1 and Q2 as lookup-tables.
4862          Q1 = qlc:q([X || X <- ets:table(E1)]),
4863          Q2 = qlc:q([X || X <- ets:table(E2)]),
4864          F = fun(J) -> qlc:q([{X,Y} || X <- Q1,
4865                                        Y <- Q2,
4866                                        element(1,X) =:= element(1,Y)],
4867                              [{join,J}])
4868              end,
4869          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4870          Q = F(merge),
4871          {1,0,0,2} = join_info(Q),
4872          R = lists:sort(qlc:e(Q)),
4873          ets:delete(E1),
4874          ets:delete(E2),
4875          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4876       ">>,
4877
4878       <<"E1 = create_ets(1, 10),
4879          E2 = create_ets(5, 15),
4880          Q = qlc:q([{X,Y} || X <- ets:table(E1),
4881                              Y <- ets:table(E2),
4882                              element(1,X) =:= element(1,Y)],
4883                    [{join,merge}]),
4884          {1,0,0,2} = join_info(Q),
4885          R = lists:sort(qlc:e(Q)),
4886          ets:delete(E1),
4887          ets:delete(E2),
4888          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4889       ">>,
4890
4891       <<"E1 = create_ets(1, 10),
4892          E2 = create_ets(5, 15),
4893          Q1 = qlc:q([Y || X <- ets:table(E1), begin Y = {X}, true end]),
4894          %% A match spec.; Q does not see Q2 as a lookup-table.
4895          %%
4896          %% OTP-6673: lookup join is considered but since there is no
4897          %% filter that can do the job of Q2, lookup join is not an option..
4898          Q2 = qlc:q([{X} || X <- ets:table(E2)]),
4899          F = fun(J) ->
4900                      qlc:q([{X,Y} || X <- Q1,
4901                                      Y <- Q2,
4902                                      element(1,X) =:= element(1,Y)],
4903                            [{join,J}])
4904              end,
4905          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4906          Q = F(any),
4907          {1,0,0,2} = join_info(Q),
4908          R = lists:sort(qlc:e(Q)),
4909          ets:delete(E1),
4910          ets:delete(E2),
4911          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {{X,X}})] =:= R
4912       ">>,
4913
4914       <<"L1 = [{1,a},{2,a},{1,b},{2,b},{1,c},{2,c}],
4915          L2 = [{b,Y} || Y <- lists:seq(1, 10000)],
4916          F = fun(J) ->
4917                      Q = qlc:q([{XX,YY} ||
4918                                    {X,XX} <- L1,
4919                                    {YY,Y} <- L2,
4920                                    X == Y],
4921                                {join,J}),
4922                      qlc:q([{XX1,YY1,XX2,YY2} ||
4923                                {XX1,YY1} <- Q,
4924                                {XX2,YY2} <- Q])
4925              end,
4926          Qm = F(merge),
4927          Qn = F(nested_loop),
4928          true = lists:sort(qlc:e(Qm)) =:= lists:sort(qlc:e(Qn))">>,
4929
4930       <<"L1 = [{{1,a},2},{{3,c},4}],
4931          L2 = [{a,{1,a}},{c,{4,d}}],
4932          Q = qlc:q([{X,Y} || {X,_} <- L1,
4933                              {_,{Y,Z}} <- L2,
4934                              X == {Y,Z}
4935                           ]),
4936          {qlc,_,[{generate,_,{qlc,_,
4937                   [{generate,_,
4938                     {qlc,_,[{generate,_,{keysort,{list,L1},1,[]}}],[]}},
4939                    {generate,_,
4940                     {qlc,_,[{generate,_,{keysort,{list,L2},2,[]}}],[]}},
4941                    _],
4942                   [{join,merge}]}}],[]}  = i(Q),
4943          [{{1,a},1}] = qlc:e(Q)">>,
4944
4945       <<"etsc(fun(E1) ->
4946                   etsc(fun(E2) ->
4947                      Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4948                                          {Z} <- ets:table(E2),   % (2)
4949                                            (Z =:= X) and
4950                                            (Y =:= a) and
4951                                            (X =:= Y) or
4952                                          (Y =:= b) and
4953                                          (Z =:= Y)]),
4954                      %% Cannot look up in (1) (X is keypos). Can look up (2).
4955                      %% Lookup join not possible (cannot look up in (1)).
4956                      %% Merge join is possible (after lookup in (2)).
4957                      {1,0,0,2} = join_info_count(Q),
4958                      {qlc,_,
4959                       [{generate,_,
4960                         {qlc,_,[{generate,_,
4961                                  {qlc,_,[{generate,_,
4962                                           {keysort,
4963                                            {table,{ets,table,_}},
4964                                                  2,[]}},_C1],[]}},
4965                                 {generate,_,
4966                                  {qlc,_,[{generate,_,
4967                                           {keysort,{table,_},1,[]}},_C2],
4968                                   []}},
4969                                 _],[{join,merge}]}},_],[]} = i(Q),
4970                      [{a,a}] = qlc:e(Q)
4971                   end, [{a}])
4972                end, [{a,1},{a,a},{b,1},{b,2}])">>,
4973
4974       <<"Q = qlc:q([{G1,G2} ||
4975                        G1<- [{1}],
4976                        G2 <- [{1}],
4977                        element(1, G1) =:= element(1, G2)]),
4978          {1,0,0,2} = join_info(Q),
4979          [{{1},{1}}] = qlc:e(Q)">>,
4980
4981       <<"Q = qlc:q([{X,Y} ||
4982                         X <- [{1}],
4983                         Y <- [{1}],
4984                         element(1, X) =:= element(1, Y)],
4985                     {join,merge}),
4986          {1,0,0,2} = join_info(Q),
4987          [{{1},{1}}] = qlc:e(Q)">>,
4988
4989       <<"%% Generator after the join-filter.
4990          Q = qlc:q([Z ||
4991                        {X} <- [{1},{2},{3}],
4992                        {Y} <- [{2},{3},{4}],
4993                        X =:= Y,
4994                        Z <- [1,2]]),
4995          {qlc,_,
4996           [{generate,_,{qlc,_,
4997                [{generate,_,{qlc,_,
4998                    [{generate,_,{keysort,{list,[{1},{2},{3}]},1,[]}}],[]}},
4999                {generate,_,{qlc,_,
5000                    [{generate,_,{keysort,{list,_},1,[]}}],[]}},_],
5001                [{join,merge}]}}, _,{generate,_,{list,_}}],[]} = i(Q),
5002          [1,2,1,2] = qlc:e(Q)">>,
5003
5004       <<"%% X and W occur twice in the pattern of the extra join handle.
5005          Q = qlc:q([{Z,W} ||
5006                        {X,Z,X} <- [{1,2,1},{1,2,2}],
5007                        {W,Y,W} <- [{a,1,a}],
5008                        X =:= Y]),
5009          [{2,a}] = qlc:e(Q)">>
5010
5011          ],
5012    run(Config, Ts),
5013
5014    %% Small examples. Returning an error term.
5015    ETs = [
5016       <<"F = fun(M) ->
5017                  qlc:q([{XX,YY} ||
5018                         {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5019                         {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5020                                    {3,c},{3,cc}],
5021                          X =:= Y],
5022                        {join,M})
5023              end,
5024          R = qlc:e(F(nested_loop)),
5025          R = qlc:e(F(merge))">>,
5026
5027       <<"F = fun(M) ->
5028                qlc:q([{XX,YY} ||
5029                       {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5030                       {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5031                                  {4,d}],
5032                        X =:= Y],
5033                      {join,M})
5034              end,
5035          R = qlc:e(F(nested_loop)),
5036          R = qlc:e(F(merge))">>,
5037
5038       <<"Q = qlc:q([{XX,YY} ||
5039                        {XX,X} <- [{b,1},{c,3}],
5040                        {Y,YY} <- [{1,a}],
5041                        X =:= Y],
5042                    {join,merge}),
5043          [{b,a}] = qlc:e(Q)">>,
5044
5045       <<"Q = qlc:q([{XX,YY} ||
5046                            {XX,X} <- [{b,1},{c,3}],
5047                            {Y,YY} <- qlc_SUITE:table_error([{1,a}], 1, err),
5048                            X =:= Y],
5049                        {join,merge}),
5050              err = qlc:e(Q)">>,
5051
5052       <<"Q = qlc:q([{XX,YY} ||
5053                            {XX,X} <- [{a,1},{aa,1}],
5054                            {Y,YY} <- [{1,a}],
5055                            X =:= Y],
5056                        {join,merge}),
5057              [{a,a},{aa,a}] = qlc:e(Q)">>,
5058
5059       <<"Q = qlc:q([{XX,YY} ||
5060                            {XX,X} <- qlc_SUITE:table_error([{a,1},{aa,1}],
5061                                                             2, err),
5062                            {Y,YY} <- [{1,a}],
5063                            X =:= Y],
5064                        {join,merge}),
5065              err = qlc:e(Q)">>,
5066
5067       <<"Q = qlc:q([{XX,YY} ||
5068                            {XX,X} <- [{a,1}],
5069                            {Y,YY} <- [{1,a},{1,aa}],
5070                            X =:= Y],
5071                        {join,merge}),
5072              [{a,a},{a,aa}]= qlc:e(Q)">>,
5073
5074       <<"Q = qlc:q([{XX,YY} ||
5075                            {XX,X} <- qlc_SUITE:table_error([{a,1}], 2, err),
5076                            {Y,YY} <- [{1,a},{1,aa}],
5077                            X =:= Y],
5078                        {join,merge}),
5079          C = qlc:cursor(Q),
5080          [{a,a}] = qlc:next_answers(C, 1),
5081          qlc:delete_cursor(C),
5082          err = qlc:e(Q)">>,
5083
5084       <<"F = fun(M) ->
5085                    qlc:q([{XX,YY} ||
5086                               {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5087                               {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},
5088                                          {2,bb},{2,bbb}],
5089                            X =:= Y],
5090                          {join,M})
5091              end,
5092              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5093              R = qlc:e(F(nested_loop)),
5094              R = qlc:e(F(merge))">>,
5095
5096
5097       <<"F = fun(M) ->
5098                   qlc:q([{XX,YY} ||
5099                          {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5100                          {Y,YY} <- qlc_SUITE:table_error([{0,a},{1,a},{1,aa},
5101                                                           {2,b},{2,bb},
5102                                                           {2,bbb}],
5103                                                          1, err),
5104                           X =:= Y],
5105                         {join,M})
5106              end,
5107              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5108              err = qlc:e(F(nested_loop)),
5109              err = qlc:e(F(merge))">>,
5110
5111       <<"Q = qlc:q([{XX,YY} ||
5112                            {XX,X} <- qlc_SUITE:table_error([], 2, err),
5113                            {Y,YY} <- [{2,b},{3,c}],
5114                            X =:= Y],
5115                        {join,merge}),
5116              err = qlc:e(Q)">>,
5117
5118       <<"Q = qlc:q([{XX,YY} ||
5119                            {XX,X} <- [{a,1},{c,3}],
5120                            {Y,YY} <- [{2,b},{3,c}],
5121                            X =:= Y],
5122                        {join,merge}),
5123              [{c,c}] = qlc:e(Q)">>,
5124
5125       <<"Q = qlc:q([{XX,YY} ||
5126                            {XX,X} <- [{a,1},{aa,1}],
5127                            {Y,YY} <- [{1,a},{1,aa}],
5128                            X =:= Y],
5129                        {join,merge}),
5130              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5131
5132       <<"Q = qlc:q([{XX,YY} ||
5133                            {XX,X} <- [{a,1},{b,2}],
5134                            {Y,YY} <- [{1,a},{1,aa}],
5135                            X =:= Y],
5136                        {join,merge}),
5137              [{a,a},{a,aa}] = qlc:e(Q)">>,
5138
5139       <<"Q = qlc:q([{XX,YY} ||
5140                            {XX,X} <- [{a,1},{b,2}],
5141                            {Y,YY} <- qlc_SUITE:table_error([{1,a},{1,aa}],
5142                                                            1, err),
5143                            X =:= Y],
5144                        {join,merge}),
5145              err = qlc:e(Q)">>,
5146
5147       <<"Q = qlc:q([{XX,YY} ||
5148                            {XX,X} <- [{a,1},{b,2}],
5149                            {Y,YY} <- [{1,a},{1,aa},{1,aaa},{1,aaaa}],
5150                            X =:= Y],
5151                        {join,merge}),
5152              [{a,a},{a,aa},{a,aaa},{a,aaaa}]= qlc:e(Q)">>,
5153
5154       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5155                            X <- [{a,1},{aa,1}],
5156                            Y <- [{1,a},{1,aa}],
5157                            element(2, X) =:= element(1, Y)],
5158                        {join,merge}),
5159              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5160
5161       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5162                            X <- [{a,1},{aa,1}],
5163                            Y <- qlc_SUITE:table_error([], 1, err),
5164                            element(2, X) =:= element(1, Y)],
5165                        {join,merge}),
5166              err = qlc:e(Q)">>,
5167
5168       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5169                            X <- qlc_SUITE:table_error([{a,1}], 2, err),
5170                            Y <- [{2,b}],
5171                            element(2, X) =:= element(1, Y)],
5172                        {join,merge}),
5173              err = qlc:e(Q)">>,
5174
5175       <<"Q = qlc:q([{XX,YY} ||
5176                  {XX,X} <- [{1,a},{'1b',b},{2,b}],
5177                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5178                  X == Y],
5179              {join,merge}),
5180          [{1,1},{'1b','1b'},{2,'1b'}] = qlc:e(Q)">>,
5181
5182       <<"Q = qlc:q([{XX,YY} ||
5183                  {XX,X} <- qlc_SUITE:table_error([{1,a},{'1b',b},{2,b}],
5184                                                  2, err),
5185                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5186                  X == Y],
5187              {join,merge}),
5188          err = qlc:e(Q)">>
5189
5190          ],
5191    run(Config, ETs),
5192
5193    %% Mostly examples where temporary files are needed while merging.
5194    FTs = [
5195       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5196          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5197          F = fun(J) ->
5198                      qlc:q([{XX,YY} ||
5199                                {XX,X} <- L1,
5200                                {Y,YY} <- L2,
5201                                X == Y],
5202                            {join,J})
5203              end,
5204          Qm = F(merge),
5205          Qn = F(nested_loop),
5206          true = qlc:e(Qm,{max_list_size, 0}) =:= qlc:e(Qn)">>,
5207
5208       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5209          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5210          Q = qlc:q([{XX,YY} ||
5211                        {XX,X} <- L1,
5212                        {Y,YY} <- L2,
5213                        X == Y],
5214                    {join,merge}),
5215          {error,_,{file_error,_,_}} =
5216               qlc:e(Q, [{max_list_size,64*1024},{tmpdir,\"/a/b/c\"}])">>,
5217
5218       <<"L1 = qlc_SUITE:table_error([{1,a},{2,a}], 2, err),
5219          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5220          F = fun(J) ->
5221                      qlc:q([{XX,YY} ||
5222                                {XX,X} <- L1,
5223                                {Y,YY} <- L2,
5224                                X == Y],
5225                            {join,J})
5226              end,
5227          Qm = F(merge),
5228          Qn = F(nested_loop),
5229          err = qlc:e(Qm, {max_list_size,64*1024}),
5230          err = qlc:e(Qn)">>,
5231
5232       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5233          L2 = qlc_SUITE:table_error([{a,Y} || Y <- lists:seq(1, 10000)],
5234                                     1, err),
5235          F = fun(J) ->
5236                      qlc:q([{XX,YY} ||
5237                                {XX,X} <- L1,
5238                                {Y,YY} <- L2,
5239                                X == Y],
5240                            {join,J})
5241              end,
5242          Qm = F(merge),
5243          Qn = F(nested_loop),
5244          err = qlc:e(Qm, {max_list_size,64*1024}),
5245          err = qlc:e(Qn)">>,
5246
5247       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)] ++
5248               [{'1b',b},{2,b}] ++ [{Y,d} || Y <- lists:seq(1, 2)],
5249          L2 = [{a,Y} || Y <- lists:seq(1, 10000)] ++
5250               [{b,'1b'}] ++ [{c,1}] ++ [{d,Y} || Y <- lists:seq(1, 10000)],
5251          F = fun(J) ->
5252                      qlc:q([{XX,YY} ||
5253                                {XX,X} <- L1,
5254                                {Y,YY} <- L2,
5255                                X == Y],
5256                            {join,J})
5257              end,
5258          Qm = F(merge),
5259          Qn = F(nested_loop),
5260          true = lists:sort(qlc:e(Qm, {max_list_size,64*1024})) =:=
5261                 lists:sort(qlc:e(Qn))">>,
5262
5263       <<"F = fun(J) ->
5264                      qlc:q([{XX,YY} ||
5265                                {XX,X} <- [{Y,a} || Y <- lists:seq(1, 2)],
5266                                {Y,YY} <- [{a,Y} || Y <- lists:seq(1,100000)],
5267                                X == Y],
5268                            {join,J})
5269              end,
5270          Qm = F(merge),
5271          Qn = F(nested_loop),
5272          true = qlc:e(Qm, {max_list_size,64*1024}) =:= qlc:e(Qn)">>,
5273
5274       %% More than one join in one QLC expression.
5275       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5276          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5277          F = fun(J) ->
5278                      Q = qlc:q([{XX,YY} ||
5279                                    {XX,X} <- L1,
5280                                    {Y,YY} <- L2,
5281                                    X == Y,
5282                                    begin XX > 1 end,
5283                                    begin YY > 9999 end],
5284                                {join,J}),
5285                      qlc:q([{XX1,YY1,XX2,YY2} ||
5286                                {XX1,YY1} <- Q,
5287                                {XX2,YY2} <- Q])
5288              end,
5289          Qm = F(merge),
5290          Qn = F(nested_loop),
5291          R1 = lists:sort(qlc:e(Qm, {max_list_size,64*1024})),
5292          R2 = lists:sort(qlc:e(Qm, {max_list_size,1 bsl 31})),
5293          true = R1 =:= lists:sort(qlc:e(Qn)),
5294          true = R1 =:= R2">>,
5295
5296       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5297          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5298          F = fun(J) ->
5299                      Q = qlc:q([{XX,YY} ||
5300                                    {XX,X} <- L1,
5301                                    {Y,YY} <- L2,
5302                                    X == Y,
5303                                    begin XX > 1 end,
5304                                    begin YY > 9999 end],
5305                                {join,J}),
5306                      qlc:q([{XX1,YY1,XX2,YY2} ||
5307                                {XX1,YY1} <- Q,
5308                                {XX2,YY2} <- Q,
5309                                throw(thrown)])
5310              end,
5311          Qm = F(merge),
5312          thrown = (catch {any_term, qlc:e(Qm, {max_list_size,64*1024})})">>,
5313
5314       <<"%% Bigger than 64*1024.
5315          T1 = {1, lists:seq(1, 20000)},
5316          L1 = [{a,T1},{b,T1}],
5317          L2 = [{T1,a},{T1,b}],
5318          F = fun(J) ->
5319                      qlc:q([{XX,YY} ||
5320                                {XX,X} <- L1,
5321                                {Y,YY} <- L2,
5322                                X == Y],
5323                            {join,J})
5324              end,
5325          Qm = F(merge),
5326          Qn = F(nested_loop),
5327          R = [{a,a},{a,b},{b,a},{b,b}],
5328          R = qlc:e(Qm, {max_list_size,64*1024}),
5329          R = qlc:e(Qn)">>,
5330
5331       <<"%% Bigger than 64*1024. No temporary files.
5332          T1 = {1, lists:seq(1, 20000)},
5333          L1 = [{a,T1},{b,T1}],
5334          L2 = [{T1,a},{T1,b}],
5335          F = fun(J) ->
5336                      qlc:q([{XX,YY} ||
5337                                {XX,X} <- L1,
5338                                {Y,YY} <- L2,
5339                                X == Y],
5340                            {join,J})
5341              end,
5342          Qm = F(merge),
5343          Qn = F(nested_loop),
5344          R = [{a,a},{a,b},{b,a},{b,b}],
5345          R = qlc:e(Qm, {max_list_size,1 bsl 31}),
5346          R = qlc:e(Qn)">>
5347
5348
5349          ],
5350    run(Config, FTs),
5351
5352    ok.
5353
5354%% Merge join optimizations (avoid unnecessary sorting).
5355join_sort(Config) when is_list(Config) ->
5356    Ts = [
5357       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5358          H1 = qlc:q([X || X <- H1_1], unique),
5359          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5360          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5361                               {_,Y} <- H2,
5362                               X =:= Y]),
5363          {1,0,0,2} = join_info(H3),
5364          [{4,4}] = qlc:e(H3)">>,
5365
5366       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5367          H1 = qlc:q([X || X <- H1_1], unique), % keeps the order
5368          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5369          H3 = qlc:q([{X,Y} || {X,_,_} <- H1, % no extra keysort
5370                               {Y,_} <- H2,   % an extra keysort
5371                               X =:= Y]),
5372          {1,0,0,3} = join_info(H3),
5373          [{1,1}] = qlc:e(H3)">>,
5374
5375       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5376          H1 = qlc:q([X || X <- H1_1], unique),
5377          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5378          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5379                               {_,Y} <- H2,
5380                               X =:= Y]),
5381          {1,0,0,3} = join_info(H3),
5382          [{2,2}] = qlc:e(H3)">>,
5383
5384       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5385          H1 = qlc:q([X || X <- H1_1], unique),
5386          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5387          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5388                               {_,Y} <- H2,
5389                               X =:= Y]),
5390          {1,0,0,3} = join_info(H3),
5391          [{2,2}] = qlc:e(H3)">>,
5392
5393       <<"H1 = qlc:sort([{1,a},{2,b},{3,c}]),
5394          %% Since H1 is sorted it is also keysorted on the first column.
5395          Q = qlc:q([{X, Y} || {X,_} <- H1,
5396                               {Y} <- [{0},{1},{2}],
5397                               X == Y]),
5398          {1,0,0,1} = join_info(Q),
5399          [{1,1},{2,2}] = qlc:e(Q)">>,
5400
5401       <<"H1 = qlc:sort([{r,a,1},{r,b,2},{r,c,3}]),
5402          Q = qlc:q([{X, Y} || {r,_,X} <- H1, % needs keysort(3)
5403                               {Y} <- [{0},{1},{2}],
5404                               X == Y]),
5405          {1,0,0,2} = join_info(Q),
5406          [{1,1},{2,2}] = qlc:e(Q)">>,
5407
5408       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
5409                           Y <- qlc:sort([{1,2},{3,4}]),
5410                           element(1, X) =:= element(2, Y)]),
5411          {1,0,0,2} = join_info_count(QH),
5412          [{4,5,6}] = qlc:e(QH)">>,
5413
5414       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6},{1,2,3}]),
5415          H1 = qlc:q([X || X <- H1_1], unique),
5416          H2 = qlc:keysort(2, [{2,1},{3,4}]),
5417          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5418                               {_,Y} <- H2,
5419                               X =:= Y]),
5420          H4 = qlc:keysort(1, [{1,2},{3,4},{4,a}]),
5421          H5 = qlc:q([{X,Y} || {X,_} <- H4,
5422                               {_,Y} <- H3,
5423                               X =:= Y]),
5424          {2,0,0,3} = join_info_count(H5),
5425          [{1,1},{4,4}]= qlc:e(H5)">>,
5426
5427       <<"
5428          H1 = qlc:keysort(2, [{1,a,u},{2,b,k},{3,c,l}]),
5429          H2 = qlc:q([{a,X,Y,a} || {1,X,u} <- H1,
5430                                   {2,Y,k} <- H1]),
5431          %% Neither H1 nor H2 need to be key-sorted
5432          %% (the columns are constant).
5433          H3 = qlc:q([{A,B,C,D,E,F,G,H} ||
5434                         {A,B,C,D} <- H2,
5435                         {E,F,G,H} <- H2,
5436                         A =:= H],
5437                     {join,merge}),
5438          {1,0,0,4} = join_info_count(H3),
5439          [{a,a,b,a,a,a,b,a}] = qlc:e(H3)">>,
5440
5441       <<"%% Q1 is sorted on X or Y.
5442          Q1 = qlc:q([{X,Y} ||
5443                         {X,_} <- qlc:keysort(1, [{1,a},{2,b}]),
5444                         {_,Y} <- qlc:keysort(2, [{aa,11},{bb,22}]),
5445                         X < Y]),
5446          [{1,11},{1,22},{2,11},{2,22}] = qlc:e(Q1),
5447          Q = qlc:q([{X,Y} ||
5448                        {X,_} <- Q1, % no need to sort Q1
5449                        {Y} <- [{0},{1},{2},{3}],
5450                        X =:= Y]),
5451          {1,0,0,3} = join_info_count(Q),
5452          [{1,1},{1,1},{2,2},{2,2}] = qlc:e(Q)">>,
5453
5454       <<"H1 = qlc:keysort([2], [{r,1},{r,2},{r,3}]),
5455          %% H1 is actually sorted, but this info is not captured.
5456          Q = qlc:q([{X, Y} || {r,X} <- H1,
5457                               {Y} <- [{0},{1},{2}],
5458                               X == Y]),
5459          {1,0,0,2} = join_info_count(Q),
5460          [{1,1},{2,2}] = qlc:e(Q)">>,
5461
5462       <<"%% Two leading constants columns and sorted objects
5463          %% implies keysorted on column 3.
5464          H1 = qlc:sort(qlc:q([{a,X,Y} || {X,Y} <- [{1,2},{2,3},{3,3}]])),
5465          H2 = qlc:q([{X,Y} ||
5466                         {a,3,X} <- H1,
5467                         {a,2,Y} <- H1,
5468                         X =:= Y]),
5469          {1,0,0,0} = join_info_count(H2),
5470          [{3,3}] = qlc:e(H2)">>,
5471
5472       <<"QH = qlc:q([{X,Y} || {X,Y} <- [{1,4},{1,3}],
5473                               {Z} <- [{1}],
5474                               X =:= Z, (Y =:= 3) or (Y =:= 4)]),
5475          {1,0,0,1} = join_info_count(QH),
5476          [{1,4},{1,3}] = qlc:e(QH)">>,
5477
5478       <<"E = ets:new(join, [ordered_set]),
5479          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
5480          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E), % no need to sort
5481                               {Y} <- [{0},{1},{2}],
5482                               X == Y], {join,merge}),
5483          {1,0,0,1} = join_info(Q),
5484          [{1,1},{2,2}] = qlc:e(Q),
5485          ets:delete(E)">>,
5486
5487       <<"H1 = qlc:sort([{r,1,a},{r,2,b},{r,3,c}]),
5488          Q = qlc:q([{X, Y} || {r,X,_} <- H1, % does not need keysort(3)
5489                               {Y} <- [{0},{1},{2}],
5490                               X == Y]),
5491          {1,0,0,1} = join_info(Q),
5492          [{1,1},{2,2}] = qlc:e(Q)">>,
5493
5494       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5495          H2 = [{a},{b}],
5496          %% Several columns in different qualifiers have initial
5497          %% constant columns.
5498          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5499          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5500                                  {Y} <- H2,
5501                                  {c1,c2,Z} <- H3,
5502                                  X =:= Z], {join,merge}),
5503          {1,0,0,3} = join_info(Q),
5504          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5505              qlc:e(Q)">>,
5506
5507       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5508          H2 = [{a},{b}],
5509          %% As the last one, but one keysort less.
5510          H3 = qlc:keysort(3,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5511          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5512                                  {Y} <- H2,
5513                                  {c1,c2,Z} <- H3,
5514                                  X =:= Z], {join,merge}),
5515          {1,0,0,2} = join_info(Q),
5516          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5517              qlc:e(Q)">>,
5518
5519       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5520          H2 = [{a},{b}],
5521          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5522          %% One generator before the joined generators.
5523          Q = qlc:q([{r,X,Y,Z} || {Y} <- H2,
5524                                  {r,X} <- H1,
5525                                  {c1,c2,Z} <- H3,
5526                                  X =:= Z], {join,merge}),
5527          {1,0,0,3} = join_info(Q),
5528          [{r,1,a,1},{r,2,a,2},{r,3,a,3},{r,1,b,1},{r,2,b,2},{r,3,b,3}] =
5529              qlc:e(Q)">>,
5530
5531       <<"H1 = [{a,1},{b,2},{c,3},{d,4}],
5532          H2 = [{a},{b}],
5533          H3 = [{c1,c2,a},{foo,bar,b},{c1,c2,c},{c1,c2,d}],
5534          %% A couple of \"extra\" filters and generators.
5535          Q = qlc:q([{X,Y,Z} || {X,_} <- H1,
5536                                {Y} <- H2,
5537                                X > Y,
5538                                {c1,c2,Z} <- H3,
5539                                {W} <- [{a},{b}],
5540                                W > a,
5541                                X =:= Z]),
5542          {1,0,0,2} = join_info(Q),
5543          [{c,a,c},{c,b,c},{d,a,d},{d,b,d}] = qlc:e(Q)">>,
5544
5545       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5546          H2 = qlc:sort([{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5547          %% H2 is sorted, no keysort necessary.
5548          %% This example shows that the 'filter-part' of the pattern
5549          %% ({c1,c2,Z}) should be evaluated _before_ the join.
5550          %% Otherwise the objects cannot be assumed to be keysort:ed on the
5551          %% third column (if merge join), and lookup-join would lookup
5552          %% more keys than necessary.
5553          Q = qlc:q([{r,X,Z} || {r,X} <- H1,
5554                                {c1,c2,Z} <- H2,
5555                                X =:= Z] ,{join,merge}),
5556          {1,0,0,1} = join_info(Q),
5557          [{r,1,1},{r,2,2},{r,3,3}] = qlc:e(Q)">>,
5558
5559       <<"H1 = [{1,a},{2,b},{3,c}],
5560          H2 = [{0,0},{1,1},{2,2}],
5561          H3 = qlc:q([{A,C,D} ||
5562                         {A,_B} <- H1,
5563                         {C,D} <- H2,
5564                         A == D, C == D]),
5565          H4 = [{1,1},{2,2},{3,3}],
5566          H5 = qlc:q([{X,Y} ||
5567                         {X,_,_} <- H3, % no need to sort this one (merge join)
5568                         {_,Y} <- H4,
5569                         X == Y]),
5570          Q = qlc:q([{X,Y} ||
5571                        {X,_} <- H5, % no need to sort this one
5572                        {Y,_} <- H4,
5573                        X == Y]),
5574          {{3,0,0,4},{3,0,0,6}} = join_info(Q),
5575          [{1,1},{2,2}] = qlc:e(Q)">>,
5576
5577       <<"%% There is an extra test (_C1, element(1, X) =:= 1) that is not
5578          %% necessary since the match spec does the same check. This can be
5579          %% improved upon.
5580          Q = qlc:q([{X,Y} ||
5581                        X <- [{2},{1}],
5582                        element(1, X) =:= 1,
5583                        Y=_ <- [{2},{1}],
5584                        element(1, X) =:= element(1, Y)]),
5585          {qlc,_,
5586              [{generate,_,{qlc,_,
5587                              [{generate,_,{qlc,_,
5588                                             [{generate,_,{list,{list,_},_}},
5589                                              _C1],[]}},
5590                               {generate,_,{qlc,_,
5591                                             [{generate,_,{list,[{2},{1}]}},
5592                                              _C2],[]}},_],
5593                              [{join,merge}]}},_],[]} = i(Q),
5594          {1,0,0,0} = join_info_count(Q),
5595          [{{1},{1}}] = qlc:e(Q)">>,
5596
5597       <<"etsc(fun(E) ->
5598                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5599                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5600                                        Y <- L,
5601                                        X =:= 1,
5602                                        Z =:= a,
5603                                        P1 =:= Y,
5604                                        X =:= element(1, Y)]),
5605                       {1,0,0,0} = join_info_count(Q),
5606                       [{1,2,a}] = qlc:e(Q)
5607               end, [{1,2,a},{3,4,b}])">>,
5608
5609       %% Merge join on Z and element(3, Y). No need to sort!
5610       <<"etsc(fun(E) ->
5611                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5612                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5613                                        Y <- L,
5614                                        (X =:= 1) or (X =:= 2),
5615                                        Z =:= a,
5616                                        P1 =:= Y,
5617                                        X =:= element(1, Y)]),
5618                       {1,0,0,0} = join_info_count(Q),
5619                       [{1,2,a}] = qlc:e(Q)
5620               end, [{1,2,a},{3,4,b}])">>,
5621
5622       <<"%% Y is constant as well as X. No keysort, which means that
5623          %% Y must be filtered before merge join.
5624          etsc(fun(E) ->
5625                       Q = qlc:q([X || {1,2}=X <- ets:table(E),
5626                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
5627                                       X =:= Y,
5628                                       element(1, X) =:= element(1, Y)]),
5629                       {1,0,0,0} = join_info_count(Q),
5630                       [{1,2}] = qlc:e(Q)
5631               end, [{1,2},{3,4}])">>
5632
5633         ],
5634    run(Config, Ts),
5635    ok.
5636
5637%% Join of more than two columns.
5638join_complex(Config) when is_list(Config) ->
5639    Ts = [{three,
5640           <<"three() ->
5641                  L = [],
5642                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5643                                        {_,Y} <- L,
5644                                        {Z,_} <- L,
5645                                        X =:= Y, Y == Z
5646                                     ]),
5647                  qlc:e(Q).">>,
5648           [],
5649           {warnings,[{3,qlc,too_complex_join}]}},
5650
5651          {two,
5652           <<"two() ->
5653                  Q = qlc:q([{X,Y,Z,W} ||
5654                      {X} <- [],
5655                      {Y} <- [],
5656                      {Z} <- [],
5657                      {W} <- [],
5658                      X =:= Y,
5659                      Z =:= W],{join,merge}),
5660                  qlc:e(Q).">>,
5661           [],
5662           {warnings,[{2,qlc,too_many_joins}]}}
5663       ],
5664
5665    compile(Config, Ts),
5666
5667    Ts2 = [{three,
5668            <<"three() ->
5669                  L = [],
5670                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5671                                        {_,Y} <- L,
5672                                        {Z,_} <- L,
5673                                        X =:= Y, Y == Z
5674                                     ]),
5675                  qlc:e(Q).">>,
5676            [],
5677            {[],
5678             ["cannot handle join of three or more generators efficiently"]}},
5679
5680          {two,
5681           <<"two() ->
5682                  Q = qlc:q([{X,Y,Z,W} ||
5683                      {X} <- [],
5684                      {Y} <- [],
5685                      {Z} <- [],
5686                      {W} <- [],
5687                      X =:= Y,
5688                      Z =:= W],{join,merge}),
5689                  qlc:e(Q).">>,
5690           [],
5691           {[],["cannot handle more than one join efficiently"]}}
5692       ],
5693
5694    compile_format(Config, Ts2),
5695
5696    ok.
5697
5698
5699%% OTP-5644. Handle the new language element M:F/A.
5700otp_5644(Config) when is_list(Config) ->
5701    Ts = [
5702       <<"Q = qlc:q([fun modul:mfa/0 || _ <- [1,2],
5703                                        is_function(fun modul:mfa/0, 0)]),
5704          [_,_] = qlc:eval(Q)">>
5705       ],
5706
5707    run(Config, Ts),
5708    ok.
5709
5710%% OTP-5195. Allow traverse functions returning terms.
5711otp_5195(Config) when is_list(Config) ->
5712    %% Several minor improvements have been implemented in OTP-5195.
5713    %% The test cases are spread all over... except these.
5714    %%
5715    %% Traverse functions returning terms.
5716
5717    Ts = [<<"L = [1,2,3],
5718             Err = {error,modul,err},
5719             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5720             Err = qlc:e(H)">>,
5721
5722          <<"Err = {error,modul,err},
5723             TravFun = fun() -> Err end,
5724             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5725             H = qlc:q([{X} || X <- H1]),
5726             Err = qlc:e(H)">>,
5727
5728          <<"L = [1,2,3],
5729             Err = {error,modul,err},
5730             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5731             C = qlc:cursor(H),
5732             R = qlc:next_answers(C, all_remaining),
5733             qlc:delete_cursor(C),
5734             Err = R">>,
5735
5736          <<"L = [1,2,3],
5737             Err = {error,modul,err},
5738             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5739             F = fun(Obj, A) -> A++[Obj] end,
5740             Err = qlc:fold(F, [], H)">>,
5741
5742          <<"Err = {error,modul,err},
5743             TravFun = fun() -> Err end,
5744             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5745             H = qlc:q([{X} || X <- H1]),
5746             F = fun(Obj, A) -> A++[Obj] end,
5747             Err = qlc:fold(F, [], H)">>,
5748
5749          <<"Q1 = qlc:append([qlc:append([ugly()]),[3]]),
5750             Q = qlc:q([X || X <- Q1]),
5751             42 = qlc:e(Q),
5752             ok.
5753
5754             ugly() ->
5755                 [apa | fun() -> 42 end].
5756             foo() -> bar">>,
5757
5758          <<"L = [1,2,3],
5759             Err = {error,modul,err},
5760             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5761             H1 = qlc:q([X || X <- H], unique),
5762             Err = qlc:e(H1)">>,
5763
5764          <<"Err = {error, module, err},
5765             L = [1,2,3],
5766             H1 = qlc:q([{X} || X <- qlc_SUITE:table_error(L, Err)]),
5767             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5768             qlc:e(H, cache_all)">>,
5769
5770          <<"Err = {error, module, err},
5771             L = [1,2,3],
5772             H1 = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5773             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5774             qlc:e(H, [cache_all,unique_all])">>,
5775
5776          <<"L = [{1},{2},{3}],
5777             H = qlc:q([X || {X} <- qlc_SUITE:table_lookup_error(L),
5778                             X =:= 2]),
5779             {error, lookup, failed} = qlc:e(H)">>,
5780
5781          %% The traverse function can return any value, but it must not
5782          %% return an improper list. Improper lists must not be given anyway.
5783          <<"{'EXIT', {{badfun,a},_}} =
5784             (catch qlc:e(qlc:q([{X} || X <- [1 | a], begin true end])))">>
5785
5786       ],
5787
5788    run(Config, Ts),
5789
5790    Ts2 = [<<"Q = qlc:q([{X,Y} || {X} <- [{1},{2},{3}],
5791                                  begin
5792                                      %% Used to generate a badly formed file
5793                                      Y = 3, true
5794                                  end,
5795                                  X =:= Y]),
5796              [{3,3}] = qlc:e(Q)">>],
5797    run(Config, Ts2),
5798
5799    ok.
5800
5801%% OTP-6038. Bug fixes: unique and keysort; cache.
5802otp_6038_bug(Config) when is_list(Config) ->
5803    %% The 'unique' option can no longer be merged with the keysort options.
5804    %% This used to return [{1,a},{1,c},{2,b},{2,d}], but since
5805    %% file_sorter:keysort now removes duplicates based on keys, the
5806    %% correct return value is [{1,a},{2,b}].
5807    Ts = [<<"H1 = qlc:q([X || X <- [{1,a},{2,b},{1,c},{2,d}]], unique),
5808             H2 = qlc:keysort(1, H1, [{unique,true}]),
5809             [{1,a},{2,b}] = qlc:e(H2)">>],
5810
5811    run(Config, Ts),
5812
5813    %% Sometimes the cache options did not empty the correct tables.
5814    CTs = [
5815       <<"Options = [cache,unique],
5816          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5817          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5818          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5819          Q = qlc:q([{X,Y} || X <- V2, Y <- V3]),
5820          R = qlc:e(Q),
5821          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5822          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5823          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5824          L = [{X,Y} || X <- L2, Y <- L3],
5825          true = R =:= L">>,
5826       <<"Options = [cache,unique],
5827          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5828          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5829          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5830          V4 = qlc:q([{X,Y} || X <- V2, Y <- V3], Options),
5831          Q = qlc:q([{X,Y} || X <- [1,2], Y <- V4]),
5832          R = qlc:e(Q),
5833          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5834          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5835          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5836          L4 = [{X,Y} || X <- L2, Y <- L3],
5837          L = [{X,Y} || X <- [1,2], Y <- L4],
5838          true = R =:= L">>
5839       ],
5840    run(Config, CTs),
5841
5842    ok.
5843
5844%% OTP-6359. dets:select() never returns the empty list.
5845otp_6359(Config) when is_list(Config) ->
5846    dets:start(),
5847    T = luna,
5848    Fname = filename(T, Config),
5849
5850    Ts = [
5851       [<<"T = luna, Fname = \"">>, Fname, <<"\",
5852           {ok, _} = dets:open_file(T, [{file,Fname}]),
5853           Q = qlc:q([F ||
5854                         F <- dets:table(T),
5855                         (F band ((1 bsl 0)) =/= 0),
5856                         true]),
5857           [] = qlc:eval(Q),
5858           ok = dets:close(T),
5859           file:delete(\"">>, Fname, <<"\"),
5860           ok">>]
5861    ],
5862
5863    run(Config, Ts),
5864    ok.
5865
5866%% OTP-6562. compressed = false (should be []) when sorting before join.
5867otp_6562(Config) when is_list(Config) ->
5868    Bug = [
5869      %% This example uses a file to sort E2 on the second column. It is
5870      %% not easy to verify that this happens; the file_sorter module's
5871      %% size option cannot be set in this case. But it is not likely
5872      %% that the default size (512 KiB) will ever change, so it should
5873      %% be future safe.
5874      <<"E1 = create_ets(1, 10),
5875         E2 = create_ets(5, 150000),
5876         Q = qlc:q([{XX,YY} ||
5877                       {X,XX} <- ets:table(E1),
5878                       {YY,Y} <- ets:table(E2),
5879                       X == Y],
5880                   {join,merge}),
5881         [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = qlc:e(Q),
5882         ets:delete(E1),
5883         ets:delete(E2)">>
5884    ],
5885    run(Config, Bug),
5886
5887    Bits = [
5888       {otp_6562_1,
5889        <<"otp_6562_1() ->
5890               Q = qlc:q([X || <<X:8>> <= <<\"hej\">>]),
5891               qlc:info(Q).
5892        ">>,
5893        [],
5894        {errors,[{2,qlc,binary_generator}],
5895         []}}
5896       ],
5897    [] = compile(Config, Bits),
5898
5899    R1 = {error,qlc,{1,qlc,binary_generator}}
5900             = qlc:string_to_handle("[X || <<X:8>> <= <<\"hej\">>]."),
5901    "1: cannot handle binary generators\n" =
5902             lists:flatten(qlc:format_error(R1)),
5903
5904    ok.
5905
5906%% OTP-6590. Bug fix (join info).
5907otp_6590(Config) when is_list(Config) ->
5908    Ts = [<<"fun(Tab1Value) ->
5909                    Q = qlc:q([T1#tab1.id || T1 <- [#tab1{id = id1,
5910                                                          value = v,
5911                                                          tab2_id = id}],
5912                                             T2 <- [#tab2{id = id}],
5913                                             T1#tab1.value =:= Tab1Value,
5914                                             T1#tab1.tab2_id =:= T2#tab2.id]),
5915                    [id1] = qlc:e(Q)
5916            end(v)">>],
5917
5918    run(Config, <<"-record(tab1, {id, tab2_id, value}).
5919                         -record(tab2, {id, value}).\n">>, Ts),
5920    ok.
5921
5922%% OTP-6673. Optimizations and fixes.
5923otp_6673(Config) when is_list(Config) ->
5924    Ts_PT =
5925        [<<"etsc(fun(E1) ->
5926                etsc(fun(E2) ->
5927                       Q = qlc:q([{A,B,C,D} ||
5928                                     {A,B} <- ets:table(E1),
5929                                     {C,D} <- ets:table(E2),
5930                                     A =:= 2, % lookup
5931                                     B =:= D, % join
5932                                     C =:= g]), % lookup invalidated by join
5933                       {qlc,_,[{generate,_,
5934                                {qlc,_,
5935                                 [{generate,_,
5936                                   {qlc,_,[{generate,_,
5937                                            {keysort,
5938                                             {list,{table,_},
5939                                              [{{'$1','$2'},[],['$_']}]},
5940                                             2,[]}},_],[]}},
5941                                  {generate,_,{qlc,_,
5942                                    [{generate,_,
5943                                      {keysort,{table,_},2,[]}}],
5944                                    []}},_],
5945                                 [{join,merge}]}},_,_],[]} = i(Q),
5946                       [{2,y,g,y}] = qlc:e(Q)
5947                     end, [{f,x},{g,y},{h,z}])
5948                 end,
5949                 [{1,x},{2,y},{3,z}])">>,
5950         <<"etsc(fun(E1) ->
5951                etsc(fun(E2) ->
5952                       Q = qlc:q([{A,B,C,D} ||
5953                                     {A,B} <- ets:table(E1),
5954                                     {C,D} <- ets:table(E2),
5955                                     A =:= 2, % lookup
5956                                     C =:= g, % lookup
5957                                     B =:= D]), % join
5958                       {qlc,_,[{generate,_,
5959                                {qlc,_,
5960                                 [{generate,_,
5961                                   {qlc,_,[{generate,_,
5962                                            {keysort,
5963                                             {list,{table,_},
5964                                              [{{'$1','$2'},[],['$_']}]},
5965                                             2,[]}},_],[]}},
5966                                  {generate,_,{qlc,_,
5967                                               [{generate,_,
5968                                                 {keysort,
5969                                                  {list,{table,_},
5970                                                   [{{'$1','$2'},[],['$_']}]},
5971                                                  2,[]}},_],[]}},_],
5972                                 [{join,merge}]}},_],[]} = i(Q),
5973                       [{2,y,g,y}] = qlc:e(Q)
5974                     end, [{f,x},{g,y},{h,z}])
5975                 end,
5976                 [{1,x},{2,y},{3,z}])">>],
5977
5978    run(Config, Ts_PT),
5979
5980    MS = ets:fun2ms(fun({X,_Y}=T) when X > 1 -> T end),
5981    Ts_RT = [
5982        [<<"%% Explicit match-spec. ets:table() ensures there is no lookup
5983            %% function, which means that lookup join will not be considered.
5984            MS = ">>, io_lib:format("~w", [MS]), <<",
5985            etsc(fun(E) ->
5986                         F = fun(J) ->
5987                                   qlc:q([{X,W} ||
5988                                             {X,_Y} <-
5989                                                 ets:table(E,{traverse,
5990                                                              {select,MS}}),
5991                                             {Z,W} <- [{1,1},{2,2},{3,3}],
5992                                             X =:= Z], {join,J})
5993                             end,
5994                         Qm = F(any),
5995                         [{2,2},{3,3}] = qlc:e(Qm),
5996                         {'EXIT',{cannot_carry_out_join,_}} =
5997                             (catch qlc:e(F(lookup)))
5998                 end, [{1,a},{2,b},{3,c}])">>],
5999
6000         <<"%% The filter 'A =< y' can be evaluated by traversing E1 using a
6001            %% match specification, but then lookup join cannot use E1 for
6002            %% looking up keys. This example shows that the filter is kept if
6003            %% lookup join is employed (otherwise it is optimized away since
6004            %% the match spec is used).
6005            etsc(fun(E1) ->
6006                         Q = qlc:q([{A,B,C,D} ||
6007                                       {A,B} <- ets:table(E1),
6008                                       {C,D} <- [{x,f},{y,g},{z,h}],
6009                                       A =< y, % kept
6010                                       A =:= C], {join,lookup}),
6011                         [{x,1,x,f},{y,2,y,g}] = lists:sort(qlc:e(Q))
6012                 end, [{x,1},{y,2},{z,3}])">>
6013
6014    ],
6015    run(Config, Ts_RT),
6016
6017    ok.
6018
6019%% OTP-6964. New option 'tmpdir_usage'.
6020otp_6964(Config) when is_list(Config) ->
6021    T1 = [
6022       <<"Q1 = qlc:q([{X} || X <- [1,2]]),
6023          {'EXIT', {badarg,_}} = (catch qlc:e(Q1, {tmpdir_usage,bad})),
6024          %% merge join
6025          F = fun(Use) ->
6026                      L1 = [{Y,a} || Y <- lists:seq(1, 2)],
6027                      L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
6028                      Q = qlc:q([{XX,YY} ||
6029                                    {XX,X} <- L1,
6030                                    {Y,YY} <- L2,
6031                                    X == Y],
6032                                {join,merge}),
6033                      qlc:e(Q, [{max_list_size,64*1024},{tmpdir_usage,Use}])
6034              end,
6035          D = erlang:system_flag(backtrace_depth, 0),
6036      try
6037          20000 = length(F(allowed)),
6038          ErrReply = F(not_allowed),
6039          {error, qlc, {tmpdir_usage,joining}} = ErrReply,
6040          \"temporary file was needed for joining\n\" =
6041              lists:flatten(qlc:format_error(ErrReply)),
6042          qlc_SUITE:install_error_logger(),
6043          20000 = length(F(warning_msg)),
6044          {warning, joining} = qlc_SUITE:read_error_logger(),
6045          20000 = length(F(info_msg)),
6046          {info, joining} = qlc_SUITE:read_error_logger(),
6047          20000 = length(F(error_msg)),
6048          {error, joining} = qlc_SUITE:read_error_logger()
6049      after
6050          _ = erlang:system_flag(backtrace_depth, D)
6051      end,
6052          qlc_SUITE:uninstall_error_logger()">>],
6053    run(Config, T1),
6054
6055    T2 = [
6056       <<"%% File sorter.
6057          T = lists:seq(1, 10000),
6058          Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
6059                     [{cache,list},unique]),
6060          Q1 = qlc:q([{X,Y,Z} ||
6061                         X <- Q0,
6062                         Y <- Q0,
6063                         Z <- Q0],
6064                     [{cache,list},unique]),
6065          Q = qlc:q([{X, Y} || Y <- [1], X <- Q1]),
6066          F = fun(Use) ->
6067                      qlc:e(Q, [{max_list_size,10000},{tmpdir_usage,Use}])
6068              end,
6069          1 = length(F(allowed)),
6070          ErrReply = F(not_allowed),
6071          {error, qlc, {tmpdir_usage,caching}} = ErrReply,
6072          \"temporary file was needed for caching\n\" =
6073              lists:flatten(qlc:format_error(ErrReply)),
6074          qlc_SUITE:install_error_logger(),
6075          1 = length(F(error_msg)),
6076          {error, caching} = qlc_SUITE:read_error_logger(),
6077          {error, caching} = qlc_SUITE:read_error_logger(),
6078          1 = length(F(warning_msg)),
6079          {warning, caching} = qlc_SUITE:read_error_logger(),
6080          {warning, caching} = qlc_SUITE:read_error_logger(),
6081          1 = length(F(info_msg)),
6082          {info, caching} = qlc_SUITE:read_error_logger(),
6083          {info, caching} = qlc_SUITE:read_error_logger(),
6084          qlc_SUITE:uninstall_error_logger()">>],
6085
6086    run(Config, T2),
6087
6088    T3 = [
6089       <<"%% sort/keysort
6090          E1 = create_ets(1, 10),
6091          E2 = create_ets(5, 50000),
6092          Q = qlc:q([{XX,YY} ||
6093                        {X,XX} <- ets:table(E1),
6094                        {YY,Y} <- ets:table(E2),
6095                        X == Y],
6096                    {join,merge}),
6097          F = fun(Use) ->
6098                      qlc:e(Q, {tmpdir_usage,Use})
6099              end,
6100          ErrReply = F(not_allowed),
6101          {error,qlc,{tmpdir_usage,sorting}} = ErrReply,
6102          \"temporary file was needed for sorting\n\" =
6103              lists:flatten(qlc:format_error(ErrReply)),
6104          qlc_SUITE:install_error_logger(),
6105          L = [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}],
6106          L = F(allowed),
6107          L = F(error_msg),
6108          {error, sorting} = qlc_SUITE:read_error_logger(),
6109          L = F(info_msg),
6110          {info, sorting} = qlc_SUITE:read_error_logger(),
6111          L = F(warning_msg),
6112          {warning, sorting} = qlc_SUITE:read_error_logger(),
6113          qlc_SUITE:uninstall_error_logger(),
6114          ets:delete(E1),
6115          ets:delete(E2)">>],
6116    run(Config, T3),
6117
6118    T4 = [
6119       <<"%% cache list
6120          etsc(fun(E) ->
6121                       Q0 = qlc:q([X || X <- ets:table(E),
6122                                        begin element(1, X) > 5 end],
6123                                  {cache,list}),
6124                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
6125                                                       Y <- Q0]),
6126                       R = [{X,Y} || X <- lists:seq(1, 5),
6127                                     Y <- lists:seq(6, 10)],
6128                       F = fun(Use) ->
6129                                   qlc:e(Q, [{max_list_size, 100*1024},
6130                                             {tmpdir_usage, Use}])
6131                           end,
6132                       R = lists:sort(F(allowed)),
6133                       qlc_SUITE:install_error_logger(),
6134                       R = lists:sort(F(info_msg)),
6135                       {info, caching} = qlc_SUITE:read_error_logger(),
6136                       R = lists:sort(F(error_msg)),
6137                       {error, caching} = qlc_SUITE:read_error_logger(),
6138                       R = lists:sort(F(warning_msg)),
6139                       {warning, caching} = qlc_SUITE:read_error_logger(),
6140                       qlc_SUITE:uninstall_error_logger(),
6141                       ErrReply = F(not_allowed),
6142                       {error,qlc,{tmpdir_usage,caching}} = ErrReply,
6143                       \"temporary file was needed for caching\n\" =
6144                           lists:flatten(qlc:format_error(ErrReply))
6145               end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
6146                                       I <- lists:seq(1, 10)])">>],
6147    run(Config, T4),
6148    ok.
6149
6150%% OTP-7238. info-option 'depth', &c.
6151otp_7238(Config) when is_list(Config) ->
6152    dets:start(),
6153    T = otp_7238,
6154    Fname = filename(T, Config),
6155
6156    ok = compile_gb_table(Config),
6157
6158    %% A few more warnings.
6159    T1 = [
6160       %% The same error message string, but with different tags
6161       %% (the strings are not compared :-(
6162       {nomatch_1,
6163        <<"nomatch_1() ->
6164               {qlc:q([X || X={X} <- []]), [t || \"a\"=\"b\" <- []]}.">>,
6165        [],
6166        %% {warnings,[{{2,30},qlc,nomatch_pattern},
6167        %%            {{2,44},v3_core,nomatch}]}},
6168        {warnings,[{2,v3_core,nomatch}]}},
6169
6170       %% Not found by qlc...
6171       {nomatch_2,
6172        <<"nomatch_2() ->
6173               qlc:q([t || {\"a\"++\"b\"} = {\"ac\"} <- []]).">>,
6174        [],
6175        {warnings,[{{2,22},v3_core,nomatch}]}},
6176
6177       {nomatch_3,
6178        <<"nomatch_3() ->
6179               qlc:q([t || [$a, $b] = \"ba\" <- []]).">>,
6180        [],
6181        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
6182        {warnings,[{2,v3_core,nomatch}]}},
6183
6184       %% Not found by qlc...
6185       {nomatch_4,
6186        <<"nomatch_4() ->
6187               qlc:q([t || \"a\"++_=\"b\" <- []]).">>,
6188        [],
6189        {warnings,[{{2,22},v3_core,nomatch}]}},
6190
6191       %% Found neither by the compiler nor by qlc...
6192       {nomatch_5,
6193        <<"nomatch_5() ->
6194               qlc:q([X || X = <<X>> <- [3]]).">>,
6195        [],
6196        []},
6197
6198       {nomatch_6,
6199        <<"nomatch_6() ->
6200               qlc:q([X || X <- [],
6201                           X =:= {X}]).">>,
6202        [],
6203        %% {warnings,[{{3,30},qlc,nomatch_filter}]}},
6204        []},
6205
6206       {nomatch_7,
6207        <<"nomatch_7() ->
6208               qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6209        [],
6210        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6211        []},
6212
6213       {nomatch_8,
6214        <<"nomatch_8() ->
6215               qlc:q([X || {X={},X=[]} <- []]).">>,
6216        [],
6217        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6218        []},
6219
6220       {nomatch_9,
6221        <<"nomatch_9() ->
6222               qlc:q([X || X <- [], X =:= {}, X =:= []]).">>,
6223        [],
6224        %% {warnings,[{{2,49},qlc,nomatch_filter}]}},
6225        []},
6226
6227       {nomatch_10,
6228        <<"nomatch_10() ->
6229               qlc:q([X || X <- [],
6230                           ((X =:= 1) or (X =:= 2)) and (X =:= 3)]).">>,
6231        [],
6232        %% {warnings,[{{3,53},qlc,nomatch_filter}]}},
6233        []},
6234
6235       {nomatch_11,
6236        <<"nomatch_11() ->
6237               qlc:q([X || X <- [], x =:= []]).">>,
6238        [],
6239        %% {warnings,[{{2,39},qlc,nomatch_filter}]}},
6240        {warnings,[{2,sys_core_fold,nomatch_guard}]}},
6241
6242       {nomatch_12,
6243        <<"nomatch_12() ->
6244               qlc:q([X || X={} <- [], X =:= []]).">>,
6245        [],
6246        %% {warnings,[{{2,42},qlc,nomatch_filter}]}},
6247        []},
6248
6249       {nomatch_13,
6250        <<"nomatch_13() ->
6251               qlc:q([Z || Z <- [],
6252                           X={X} <- [],
6253                           Y={Y} <- []]).">>,
6254        [],
6255        %% {warnings,[{{3,29},qlc,nomatch_pattern},
6256        %%            {{4,29},qlc,nomatch_pattern}]}},
6257        []},
6258
6259       {nomatch_14,
6260        <<"nomatch_14() ->
6261               qlc:q([X || X={X} <- [],
6262                           1 > 0,
6263                           1 > X]).">>,
6264        [],
6265        %% {warnings,[{{2,29},qlc,nomatch_pattern}]}},
6266        []},
6267
6268       {nomatch_15,
6269        <<"nomatch_15() ->
6270              qlc:q([{X,Y} || X={X} <- [1],
6271                              Y <- [1],
6272                              1 > 0,
6273                              1 > X]).">>,
6274        [],
6275        %% {warnings,[{{2,32},qlc,nomatch_pattern}]}},
6276        []},
6277
6278       %% Template warning.
6279       {nomatch_template1,
6280        <<"nomatch_template1() ->
6281               qlc:q([{X} = {} || X <- []]).">>,
6282        [],
6283        {warnings,[{2,sys_core_fold,no_clause_match}]}}
6284         ],
6285    [] = compile(Config, T1),
6286
6287    %% 'depth' is a new option used by info()
6288    T2 = [
6289       %% Firstly: lists
6290       <<"L = [[a,b,c],{a,b,c},[],<<\"foobar\">>],
6291          Q = qlc:q([{X} || X <- L]),
6292          {call, _,
6293           {remote,_,{atom,_,ets},{atom,_,match_spec_run}},
6294           [{cons,_,{atom,_,'...'},
6295             {cons,_,{atom,_,'...'},
6296              {cons,_,{nil,_},{cons,_,{atom,_,'...'},{nil,_}}}}},
6297            _]} = qlc:info(Q, [{format,abstract_code},{depth,0}]),
6298
6299          {call,_,_,
6300           [{cons,_,{cons,_,{atom,_,'...'},{nil,_}},
6301             {cons,_,
6302              {tuple,_,[{atom,_,'...'}]},
6303              {cons,_,{nil,_},
6304               {cons,_,
6305                {bin,_,
6306                 [{_,_,{_,_,$.},_,_},
6307                  {_,_,{_,_,$.},_,_},
6308                  {_,_,{_,_,$.},_,_}]},
6309                {nil,_}}}}},
6310            _]} = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6311
6312          {call,_,
6313           _,
6314          [{cons,_,{cons,_,{atom,_,a},{atom,_,'...'}},
6315            {cons,_,
6316             {tuple,_,[{atom,_,a},{atom,_,'...'}]},
6317             {cons,_,{nil,_},
6318              {cons,_,
6319               {bin,_,
6320                [{_,_,{_,_,$f},_,_},
6321                 {_,_,{_,_,$.},_,_},
6322                 {_,_,{_,_,$.},_,_},
6323                 {_,_,{_,_,$.},_,_}]},
6324               {nil,_}}}}},
6325          _]} = qlc:info(Q, [{format,abstract_code},{depth,2}]),
6326
6327          {call,_,_,
6328           [{cons,_,
6329             {cons,_,{atom,_,a},{cons,_,{atom,_,b},{atom,_,'...'}}},
6330             {cons,_,
6331              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,'...'}]},
6332              {cons,_,{nil,_},
6333               {cons,_,
6334                {bin,_,
6335                 [{_,_,{_,_,$f},_,_},
6336                  {_,_,{_,_,$o},_,_},_,_,_]},
6337                {nil,_}}}}},
6338            _]} = qlc:info(Q, [{format,abstract_code},{depth,3}]),
6339
6340          {call,_,_,
6341           [{cons,_,
6342             {cons,_,
6343              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6344             {cons,_,
6345              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6346              {cons,_,{nil,_},
6347               {cons,_,
6348                {bin,_,
6349                 [{_,_,{_,_,$f},_,_},
6350                  {_,_,{_,_,$o},_,_},
6351                  {_,_,{_,_,$o},_,_},
6352                  {_,_,{_,_,$b},_,_},
6353                  {_,_,{_,_,$a},_,_},
6354                  {_,_,{_,_,$r},_,_}]},
6355                {nil,_}}}}},
6356            _]} = qlc:info(Q, [{format,abstract_code},{depth,10}]),
6357
6358          {call,_,_,
6359           [{cons,_,
6360             {cons,_,
6361              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6362             {cons,_,
6363              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6364              {cons,_,{nil,_},
6365               {cons,_,
6366                {bin,_,
6367                 [{_,_,{_,_,$f},_,_},
6368                  {_,_,{_,_,$o},_,_},
6369                  {_,_,{_,_,$o},_,_},
6370                  {_,_,{_,_,$b},_,_},
6371                  {_,_,{_,_,$a},_,_},
6372                  {_,_,{_,_,$r},_,_}]},
6373                {nil,_}}}}},
6374            _]} = qlc:info(Q, [{format,abstract_code},{depth,infinity}])">>,
6375
6376       %% Secondly: looked up keys
6377       <<"F = fun(D) ->
6378                etsc(fun(E) ->
6379                       Q = qlc:q([C || {N,C} <- ets:table(E),
6380                                       (N =:= {2,2}) or (N =:= {3,3})]),
6381                       F = qlc:info(Q, [{format,abstract_code},{depth,D}]),
6382                       {call,_,_,[{call,_,_,[_Fun,Values]},_]} = F,
6383                       [b,c] = lists:sort(qlc:eval(Q)),
6384                       Values
6385                     end, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}])
6386              end,
6387
6388          [{cons,_,{atom,_,'...'},{cons,_,{atom,_,'...'},{nil,_}}},
6389           {cons,_,
6390            {tuple,_,[{atom,_,'...'}]},
6391            {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}},
6392           {cons,_,
6393            {tuple,_,[{integer,_,2},{atom,_,'...'}]},
6394            {cons,_,{tuple,_,[{integer,_,3},{atom,_,'...'}]},{nil,_}}},
6395           {cons,_,
6396            {tuple,_,[{integer,_,2},{integer,_,2}]},
6397            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}},
6398           {cons,_,
6399            {tuple,_,[{integer,_,2},{integer,_,2}]},
6400            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}}] =
6401              lists:map(F, [0,1,2,3,infinity])">>,
6402       [<<"T = otp_7238, Fname = \"">>, Fname, <<"\",
6403           {ok, _} = dets:open_file(T, [{file,Fname}]),
6404           ok = dets:insert(T, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}]),
6405           Q = qlc:q([C || {N,C} <- dets:table(T),
6406                           (N =:= {2,2}) or (N =:= {3,3})]),
6407           F = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6408           [b,c] = lists:sort(qlc:eval(Q)),
6409           {call,_,_,
6410            [{call,_,_,
6411              [_,
6412               {cons,_,
6413                {tuple,_,[{atom,_,'...'}]},
6414                {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}]},
6415             _]} = F,
6416           ok = dets:close(T),
6417           file:delete(\"">>, Fname, <<"\")">>],
6418
6419       %% Thirdly: format_fun has been extended (in particular: gb_table)
6420       <<"T = gb_trees:from_orddict([{{1,a},w},{{2,b},v},{{3,c},u}]),
6421          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
6422                           ((X =:= 1) or (X =:= 2)),
6423                           ((Y =:= a) or (Y =:= b) or (Y =:= c))]),
6424          {call,_,_,
6425           [{call,_,_,
6426             [{'fun',_,
6427               {clauses,
6428                [{clause,_,_,[],
6429                  [{'case',_,
6430                    {call,_,_,
6431                     [_,
6432                      {call,_,_,
6433                       [{cons,_,
6434                         {tuple,_,[{atom,_,'...'}]},
6435                         {cons,_,
6436                          {tuple,_,[{atom,_,'...'}]},
6437                          {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}]}]},
6438                    [_,_]}]}]}},
6439              {cons,_,
6440               {tuple,_,[{atom,_,'...'}]},
6441               {cons,_,
6442                {tuple,_,[{atom,_,'...'}]},
6443                {cons,_,
6444                 {tuple,_,[{atom,_,'...'}]},
6445                 {cons,_,
6446                  {tuple,_,[{atom,_,'...'}]},
6447                  {cons,_,
6448                   {tuple,_,[{atom,_,'...'}]},
6449                   {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}}}}]},
6450            {call,_,_,
6451             [{cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}]}]} =
6452            qlc:info(QH, [{format,abstract_code},{depth,1}])">>,
6453       <<"T1 = [{1,1,a},{2,2,b},{3,3,c},{4,4,d}],
6454          T2 = [{x,1},{y,1},{z,2}],
6455          QH1 = T1,
6456          T = gb_trees:from_orddict(T2),
6457          QH2 = qlc:q([X || {_,X} <- gb_table:table(T)], cache),
6458          Q = qlc:q([{X1,X2,X3} || {X1,X2,X3} <- QH1,
6459                                   Y2 <- QH2,
6460                                   X2 =:= Y2]),
6461          {block,_,
6462           [{match,_,_,
6463             {call,_,_,
6464              [{lc,_,_,
6465                [{generate,_,_,
6466                  {call,_,_,
6467                   [{call,_,_,
6468                     [{cons,_,
6469                       {tuple,_,[{atom,_,'...'}]},
6470                       {atom,_,'...'}}]}]}}]},
6471               _]}},
6472            {call,_,_,
6473             [{lc,_,_,
6474               [{generate,_,_,
6475                 {cons,_,{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}}},
6476                _,_]}]}]} =
6477              qlc:info(Q, [{format,abstract_code},{depth, 1},
6478                           {n_elements,1}])">>,
6479       <<"L = [{{key,1},a},{{key,2},b},{{key,3},c}],
6480          T = gb_trees:from_orddict(orddict:from_list(L)),
6481          Q = qlc:q([K || {K,_} <- gb_table:table(T),
6482                                   (K =:= {key,1}) or (K =:= {key,2})]),
6483{call,_,_,
6484 [{call,_,_,
6485   [{'fun',_,
6486     {clauses,
6487      [{clause,_,_,[],
6488        [{'case',_,
6489          {call,_,_,
6490           [_,
6491            {call,_,_,
6492             [{cons,_,
6493               {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6494               {cons,_,
6495                {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6496                {cons,_,
6497                 {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6498                 {nil,_}}}}]}]},
6499          _}]}]}},
6500    {cons,_,
6501     {tuple,_,[{atom,_,key},{atom,_,'...'}]},
6502     {cons,_,{tuple,_,[{atom,_,key},{atom,_,'...'}]},{nil,_}}}]},
6503  {call,_,
6504   {remote,_,{atom,_,ets},{atom,_,match_spec_compile}},
6505   [{cons,_,
6506     {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6507     {nil,_}}]}]} =
6508          qlc:info(Q, [{format,abstract_code},{depth, 2}])">>
6509
6510         ],
6511    run(Config, T2),
6512
6513    T3 = [
6514%%        {nomatch_6,
6515%%         <<"nomatch_6() ->
6516%%                qlc:q([X || X <- [],
6517%%                            X =:= {X}]).">>,
6518%%         [],
6519%%         {[],["filter evaluates to 'false'"]}},
6520
6521%%        {nomatch_7,
6522%%         <<"nomatch_7() ->
6523%%                qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6524%%         [],
6525%%         {[],["pattern cannot possibly match"]}}
6526       ],
6527    compile_format(Config, T3),
6528
6529    %% *Very* simple test - just check that it doesn't crash.
6530    Type = [{cres,
6531             <<"Q = qlc:q([X || {X} <- []]),
6532                {'EXIT',{{badfun,_},_}} = (catch qlc:e(Q))">>,
6533             [type_checker],
6534             []}],
6535    run(Config, Type),
6536
6537    ok.
6538
6539%% OTP-7114. Match spec, table and duplicated objects...
6540otp_7114(Config) when is_list(Config) ->
6541    Ts = [<<"T = ets:new(t, [bag]),
6542             [ets:insert(T, {t, I, I div 2}) || I <- lists:seq(1,10)],
6543             Q1 = qlc:q([element(3, E) || E <- ets:table(T)]),
6544             [0,1,1,2,2,3,3,4,4,5] = lists:sort(qlc:e(Q1)),
6545             [0,1,2,3,4,5] = qlc:e(Q1, unique_all),
6546             [0,1,2,3,4,5] = qlc:e(qlc:sort(Q1), unique_all),
6547             [0,1,2,3,4,5] = qlc:e(qlc:sort(qlc:e(Q1)), unique_all),
6548             ets:delete(T),
6549             ok">>],
6550    run(Config, Ts).
6551
6552%% OTP-7232. qlc:info() bug (pids, ports, refs, funs).
6553otp_7232(Config) when is_list(Config) ->
6554    Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
6555                  erlang:make_ref()],
6556             \"[fun math:sqrt/1,<0.4.1>,#Ref<\" ++ _  = qlc:info(L),
6557             {call,_,
6558               {remote,_,{atom,_,qlc},{atom,_,sort}},
6559               [{cons,_,
6560                      {'fun',_,{function,{atom,_,math},{atom,_,sqrt},_}},
6561                      {cons,_,
6562                            {string,_,\"<0.4.1>\"}, % could use list_to_pid..
6563                            {cons,_,{string,_,\"#Ref<\"++_},{nil,_}}}},
6564                {nil,_}]} =
6565              qlc:info(qlc:sort(L),{format,abstract_code})">>,
6566
6567          <<"Q1 = qlc:q([X || X <- [55296,56296]]),
6568             Q = qlc:sort(Q1, {order, fun(A,B)-> A>B end}),
6569             \"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" =
6570                format_info(Q, true),
6571             AC = qlc:info(Q, {format, abstract_code}),
6572             \"qlc:sort([55296,56296], [{order,fun '-function/0-fun-2-'/2}])\" =
6573                binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>,
6574
6575         %% OTP-7234. erl_parse:abstract() handles bit strings
6576          <<"Q = qlc:sort([<<17:9>>]),
6577             \"[<<8,1:1>>]\" = qlc:info(Q)">>
6578
6579         ],
6580    run(Config, Ts).
6581
6582%% OTP-7552. Merge join bug.
6583otp_7552(Config) when is_list(Config) ->
6584    %% The poor performance cannot be observed unless the
6585    %% (redundant) join filter is skipped.
6586    Ts = [<<"Few = lists:seq(1, 2),
6587             Many = lists:seq(1, 10),
6588             S = [d,e],
6589             L1 = [{Y,a} || Y <- Few] ++ [{'1b',b},{2,b}] ++
6590                    [{Y,X} || X <- S, Y <- Few],
6591             L2 = [{a,Y} || Y <- Many] ++
6592                    [{b,'1b'}] ++ [{c,1}] ++
6593                    [{X,Y} || X <- S, Y <- Many],
6594                   F = fun(J) ->
6595                               qlc:q([{XX,YY} ||
6596                                         {XX,X} <- L1,
6597                                         {Y,YY} <- L2,
6598                                         X == Y],
6599                                     {join,J})
6600                       end,
6601                   Qm = F(merge),
6602                   Qn = F(nested_loop),
6603                   true = lists:sort(qlc:e(Qm, {max_list_size,20})) =:=
6604                          lists:sort(qlc:e(Qn))">>],
6605    run(Config, Ts).
6606
6607%% OTP-7714. Merge join bug.
6608otp_7714(Config) when is_list(Config) ->
6609    %% The original example uses Mnesia. This one does not.
6610    Ts = [<<"E1 = ets:new(set,[]),
6611             true = ets:insert(E1, {a,1}),
6612             E2 = ets:new(set,[]),
6613             _ = [true = ets:insert(E2, {I, 1}) ||
6614                     I <- lists:seq(1, 3)],
6615             Q = qlc:q([{A,B} ||
6616                           {A,I1} <- ets:table(E1),
6617                           {B,I2} <- ets:table(E2),
6618                           I1 =:= I2],{join,merge}),
6619             [{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)),
6620             ets:delete(E1),
6621             ets:delete(E2)">>],
6622    run(Config, Ts).
6623
6624%% OTP-11758. Bug.
6625otp_11758(Config) when is_list(Config) ->
6626    Ts = [<<"T = ets:new(r, [{keypos, 2}]),
6627             L = [{rrr, xxx, aaa}, {rrr, yyy, bbb}],
6628             true = ets:insert(T, L),
6629             QH = qlc:q([{rrr, B, C} || {rrr, B, C} <- ets:table(T),
6630                              (B =:= xxx) or (B =:= yyy) and (C =:= aaa)]),
6631             [{rrr,xxx,aaa}] = qlc:e(QH),
6632             ets:delete(T)">>],
6633    run(Config, Ts).
6634
6635%% OTP-6674. match/comparison.
6636otp_6674(Config) when is_list(Config) ->
6637
6638    ok = compile_gb_table(Config),
6639
6640    Ts = [%% lookup join
6641          <<"E = ets:new(join, [ordered_set]),
6642             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6643             Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6644                                  {Y} <- [{0},{1},{2}],
6645                                  X == Y]),
6646             {0,1,0,0} = join_info(Q),
6647             [{1,1},{2,2}] = qlc:e(Q),
6648             ets:delete(E)">>,
6649
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             {block,_,
6657              [_,
6658               {match,_,_,
6659                 {call,_,_,
6660                  [{lc,_,_,
6661                    [_,_,{op,_,'==',_,_}]},
6662                   {cons,_,
6663                    {tuple,_,[{atom,_,join},{atom,_,lookup}]},_}]}},
6664               _]} = qlc:info(Q, {format, abstract_code}),
6665             [{1,1},{2,2}] = qlc:e(Q),
6666             ets:delete(E)">>,
6667
6668       <<"E = ets:new(join, [set]),
6669          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6670                               {Y} <- [{0},{1},{2}],
6671                               X == Y], {join, lookup}),
6672          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(Q)),
6673          ets:delete(E)">>,
6674
6675       %% Lookup join possible in both directions.
6676       <<"E1 = ets:new(join, [ordered_set]),
6677          E2 = ets:new(join, [set]),
6678          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6679          true = ets:insert(E2, [{0},{1},{2}]),
6680          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6681                               {Y} <- ets:table(E2),
6682                               X == Y],{join,lookup}), % skipped
6683          {qlc,_,
6684            [{generate,_,
6685                 {qlc,_,
6686                     [{generate,_,
6687                          {qlc,_,[{generate,_,{table,{ets,table,[_]}}}],[]}},
6688                      {generate,_,{table,{ets,table,[_]}}},
6689                      _],
6690                     [{join,lookup}]}}],
6691            []} = qlc:info(Q, {format,debug}),
6692          {0,1,0,0} = join_info(Q),
6693          [{1.0,1},{2,2}] = lists:sort(qlc:e(Q)),
6694          ets:delete(E1),
6695          ets:delete(E2)">>,
6696       <<"E1 = ets:new(join, [ordered_set]),
6697          E2 = ets:new(join, [set]),
6698          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6699          true = ets:insert(E2, [{0},{1},{2}]),
6700          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6701                               {Y} <- ets:table(E2),
6702                               X =:= Y],{join,merge}), % not skipped
6703          {1,0,0,1} = join_info(Q),
6704          [{2,2}] = qlc:e(Q),
6705          ets:delete(E1),
6706          ets:delete(E2)">>,
6707       <<"E1 = ets:new(join, [ordered_set]),
6708          E2 = ets:new(join, [set]),
6709          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6710          true = ets:insert(E2, [{0},{1},{2}]),
6711          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6712                               {Y} <- ets:table(E2),
6713                               X =:= Y],{join,lookup}), % skipped
6714          {qlc,_,
6715           [{generate,_,
6716             {qlc,_,
6717              [{generate,_,
6718                {qlc,_,
6719                 [{generate,_,{table,{ets,table,[_]}}}],
6720                 []}},
6721               {generate,_,{table,{ets,table,[_]}}},
6722               _],
6723              [{join,lookup}]}}],
6724            []} = qlc:info(Q, {format,debug}),
6725          {0,1,0,0} = join_info(Q),
6726          [{2,2}] = qlc:e(Q),
6727          ets:delete(E1),
6728          ets:delete(E2)">>,
6729       <<"E1 = ets:new(join, [ordered_set]),
6730          E2 = ets:new(join, [set]),
6731          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6732          true = ets:insert(E2, [{0},{1},{2}]),
6733          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6734                               {Y} <- ets:table(E2),
6735                               %% Independent of term comparison:
6736                               X =:= Y, X == Y]),
6737          {0,1,0,0} = join_info(Q),
6738          [{2,2}] = qlc:e(Q),
6739          ets:delete(E1),
6740          ets:delete(E2)">>,
6741
6742       <<"E = ets:new(join, [ordered_set]),
6743          true = ets:insert(E, [{1,1},{2,2},{3,c}]),
6744          Q = qlc:q([{X, Y} || {X,Z} <- ets:table(E),
6745                               {Y} <- [{0},{1},{2}],
6746                               X == Z, Y == Z]), % cannot skip (yet)
6747          {qlc,_,
6748            [{generate,_,
6749                 {qlc,_,[_,_,_],[{join,lookup}]}},
6750             _,_],[]} = qlc:info(Q,{format,debug}),
6751          {0,1,0,0} = join_info(Q),
6752          [{1,1},{2,2}] = qlc:e(Q),
6753          ets:delete(E)">>,
6754
6755       %% The following moved here from skip_filters. It was buggy!
6756       <<"etsc(fun(E) ->
6757                 A = 3,
6758                 Q = qlc:q([X || X <- ets:table(E),
6759                                 A == element(1,X)]),
6760                 {table, _} = i(Q),
6761                 case qlc:e(Q) of
6762                       [{3},{3.0}] -> ok;
6763                       [{3.0},{3}] -> ok
6764                 end,
6765                 false = lookup_keys(Q)
6766         end, [{3},{3.0},{c}])">>,
6767    <<"H1 = qlc:sort([{{192,192.0},1,a},{{192.0,192.0},2,b},{{192,192.0},3,c}]),
6768       Q = qlc:q([{X, Y} || {{A,B},X,_} <- H1, % does not need keysort(3)
6769                            A == 192, B =:= 192.0,
6770                            {Y} <- [{0},{1},{2}],
6771                            X == Y]),
6772       A0 = erl_anno:new(0),
6773       {block,A0,
6774         [{match,_,_,
6775           {call,_,_,
6776            [{lc,_,_,
6777              [_,
6778               %% Has to compare extra constant:
6779               {op,_,'==',
6780                {tuple,_,[{integer,_,192},{float,_,192.0}]},
6781                {call,_,{atom,_,element},[{integer,_,1},{var,_,'P0'}]}}]}]}},
6782          _,_,
6783          {call,_,_,
6784           [{lc,_,_,
6785             [_,
6786              %% The join filter has been skipped.
6787              {op,_,'==',{var,_,'A'},{integer,_,192}},
6788              {op,_,'=:=',{var,_,'B'},{float,_,192.0}}]}]}]}
6789      = qlc:info(Q, {format,abstract_code}),
6790       {1,0,0,1} = join_info(Q),
6791       [{1,1},{2,2}] = qlc:e(Q)">>,
6792
6793    %% Does not handle more than one lookup value (conjunctive).
6794    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6795       H = qlc:q([X || {X,_} <- gb_table:table(T),
6796                                X =:= 1 andalso X == 1.0]),
6797       false = lookup_keys(H),
6798       [1] = qlc:e(H)">>,
6799
6800    %% EqualConstants...
6801    <<"etsc(fun(E) ->
6802                Q = qlc:q([{X,Y} || {X} <- ets:table(E),
6803                                {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6804                                X =:= {1}, X == {1.0},
6805                                X == Y], {join, merge}),
6806                [{{1},{1}},{{1},{1.0}}] = lists:sort(qlc:e(Q)),
6807                false = lookup_keys(Q)
6808         end, [{{1}}, {{2}}])">>,
6809
6810    <<"T = gb_trees:from_orddict([{foo,{1}}, {bar,{2}}]),
6811       Q = qlc:q([{X,Y} || {_,X} <- gb_table:table(T),
6812                       {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6813                         (X =:= {1}) or (X == {2}),
6814                         (X == {1.0}) or (X =:= {2.0}),
6815                       X == Y], {join, merge}),
6816       [{{1},{1}},{{1},{1.0}}] = qlc:e(Q)">>,
6817
6818    %% Compare key
6819    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6820       H = qlc:q([X || {X,_} <- gb_table:table(T),
6821                       X == 1]),
6822       [1] = lookup_keys(H),
6823       [1] = qlc:e(H)">>,
6824    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6825       H = qlc:q([X || {X,_} <- gb_table:table(T),
6826                       X == 1.0]),
6827       [1.0] = lookup_keys(H), % this is how gb_table works...
6828       [1.0] = qlc:e(H)">>,
6829    <<"etsc(fun(E) ->
6830                   H = qlc:q([X || {X,_} <- ets:table(E),
6831                                   X == 1.0]),
6832                   [1] = qlc:e(H), % and this is how ETS works.
6833                   [1.0] = lookup_keys(H)
6834           end, [ordered_set], [{1,a},{2,b}])">>,
6835
6836    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6837       H = qlc:q([X || {X,_} <- gb_table:table(T),
6838                       X =:= 2]),
6839       [2] = lookup_keys(H),
6840       %% Cannot (generally) remove the matching filter (the table
6841       %% compares the key). But note that gb_table returns the given
6842       %% term as key, so in this case the filter _could_ have been removed.
6843       %% However, there is no callback to inform qlc about that.
6844       {call,_,_,
6845             [_,{call,_,_,
6846               [{cons,_,{tuple,_,
6847                  [_,{cons,_,
6848                    {tuple,_,[{atom,_,'=:='},{atom,_,'$1'},{integer,_,2}]},
6849                    _},_]},_}]}]} =  qlc:info(H, {format,abstract_code}),
6850       [2] = qlc:e(H)">>,
6851    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6852       H = qlc:q([X || {X,_} <- gb_table:table(T),
6853                       X =:= 2.0]),
6854       %% Just shows that the term (not the key) is returned.
6855       [2.0] = lookup_keys(H),
6856       [2.0] = qlc:e(H)">>,
6857
6858    <<"I = 1,
6859       T = gb_trees:from_orddict([{1,a},{2,b}]),
6860       H = qlc:q([X || {X,_} <- gb_table:table(T),
6861                       X == I]), % imported variable
6862       [1] = lookup_keys(H),
6863       {call,_,_,
6864             [_,{call,_,_,
6865               [{cons,_,
6866                 {tuple,_,
6867                  [{tuple,_,[{atom,_,'$1'},{atom,_,'_'}]},
6868                   {nil,_}, % the filter has been skipped
6869                   {cons,_,{atom,_,'$1'},_}]},
6870                 _}]}]} = qlc:info(H, {format, abstract_code}),
6871       [1] = qlc:e(H)">>,
6872    <<"I = 2,
6873       T = gb_trees:from_orddict([{1,a},{2,b}]),
6874       H = qlc:q([X || {X,_} <- gb_table:table(T),
6875                       X =:= I]),
6876       [2] = lookup_keys(H),
6877       {call,_,_,
6878            [_,{call,_,_,
6879              [{cons,_,{tuple,_,
6880                 [_,{cons,_,
6881                   {tuple,_,
6882                    [{atom,_,'=:='},
6883                     {atom,_,'$1'},
6884                     {tuple,_,[{atom,_,const},{integer,_,2}]}]},
6885                   _},_]},
6886                _}]}]} = qlc:info(H, {format, abstract_code}),
6887          [2] = qlc:e(H)">>,
6888
6889    <<"etsc(fun(E) ->
6890                 Q = qlc:q([X || {X,_} <- ets:table(E),
6891                                 X =:= a]), % skipped
6892                 [a] = qlc:e(Q),
6893                 {list,{table,_},_} = i(Q),
6894                 [a] = lookup_keys(Q)
6895            end, [ordered_set], [{a,1},{b,2},{3,c}])">>,
6896
6897    %% Does not find that if for instance X =:= {1} then the filter
6898    %% X == {1} can be removed.
6899    <<"etsc(fun(E) ->
6900                Q = qlc:q([X || {X} <- ets:table(E),
6901                                X =:= {1}, X == {1.0}]),
6902                [{1}] = qlc:e(Q),
6903                [{1}] = lookup_keys(Q)
6904         end, [{{1}}, {{2}}])">>,
6905    <<"etsc(fun(E) ->
6906                Q = qlc:q([X || {X} <- ets:table(E),
6907                                X =:= {1}, X == {1.0}]),
6908                [{1}] = qlc:e(Q),
6909                false = lookup_keys(Q)
6910         end, [ordered_set], [{{1}}, {{2}}])">>,
6911    <<"etsc(fun(E) ->
6912                Q = qlc:q([X || {X} <- ets:table(E),
6913                                X == {1.0}, X =:= {1}]),
6914                [{1}] = qlc:e(Q),
6915                [{1}] = lookup_keys(Q)
6916         end, [{{1}}, {{2}}])">>,
6917    <<"etsc(fun(E) ->
6918                Q = qlc:q([X || {X} <- ets:table(E),
6919                                X == {1.0}, X =:= {1}]),
6920                [{1}] = qlc:e(Q),
6921                false = lookup_keys(Q)
6922         end, [ordered_set], [{{1}}, {{2}}])">>,
6923
6924    <<"E = ets:new(apa, []),
6925       true = ets:insert(E, [{1,a},{2,b}]),
6926       {'EXIT', {badarg, _}} =
6927              (catch qlc_SUITE:bad_table_key_equality(E)),
6928       ets:delete(E)">>,
6929
6930    <<"etsc(fun(E) ->
6931           Q = qlc:q([X || {X} <- ets:table(E),
6932                               X =:= 1, X =:= is_integer(X)]),
6933           [] = qlc:e(Q),
6934           [1] = lookup_keys(Q)
6935       end, [{1}, {2}])">>,
6936
6937    <<"etsc(fun(E) ->
6938                 Q = qlc:q([X || {X=1} <- ets:table(E),
6939                                 X =:= is_integer(X)]),
6940                 {call,_,_,
6941                  [{lc,_,_,
6942                    [_,
6943                     {op,_,'=:=',
6944                      {var,_,'X'},
6945                      {call,_,
6946                       {atom,_,is_integer},
6947                       [{var,_,'X'}]}}]}]} =
6948             qlc:info(Q, {format, abstract_code}),
6949             [] = qlc:e(Q),
6950             [1] = lookup_keys(Q)
6951         end, [{1}, {2}])">>,
6952
6953    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6954       H = qlc:q([X || {X,Y} <- gb_table:table(T),
6955                                Y =:= a, true, X =:= 1]),
6956       [1] = lookup_keys(H),
6957       [1] = qlc:e(H)">>,
6958
6959    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6960       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6961                       B == 1]), % skipped
6962       [{1.0, 1}] = qlc:e(H),
6963       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6964    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6965       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6966                    B == 1.0]), % skipped
6967       [{1.0, 1.0}] = qlc:e(H), % this is how gb_table works...
6968       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6969    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6970       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6971                       B =:= 1.0]), % not skipped
6972       [{1.0, 1.0}] = qlc:e(H),
6973       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6974    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6975       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6976                       B =:= 1]), % not skipped
6977       [{1.0, 1}] = qlc:e(H),
6978       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6979
6980    <<"%% The imported variables do not interfere with join.
6981       E = ets:new(join, [ordered_set]),
6982       {A, B} = {1,1},
6983       true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6984       Q = qlc:q([{X, Y} || {X,_Z} <- ets:table(E),
6985                            {Y} <- [{0},{1},{2}],
6986                            X =:= A, Y =:= B,
6987                            Y == X], % skipped
6988                {join, merge}),
6989       [{1,1}] = qlc:e(Q),
6990       {qlc,_,
6991           [{generate,_,
6992             {qlc,_,
6993              [{generate,_,
6994                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]}},
6995               {generate,_,
6996                {qlc,_,[{generate,_,{list,_,_}},_],[]}},
6997               _],
6998              [{join,merge}]}}],
6999           []} = qlc:info(Q, {format, debug}),
7000       ets:delete(E)">>,
7001
7002    <<"% An old bug: usort() should not be used when matching values
7003       etsc(fun(E) ->
7004                   I = 1,
7005                   H = qlc:q([X || {X,_} <- ets:table(E),
7006                                   X =:= 1.0 orelse X =:= I]),
7007                   [1] = qlc:e(H),
7008                   [1.0] = lookup_keys(H) % do not look up twice
7009            end, [set], [{1,a},{2,b}])">>,
7010    <<"etsc(fun(E) ->
7011                   H = qlc:q([X || {X,_} <- ets:table(E),
7012                                    X =:= 1.0 orelse X == 1]),
7013                   [1] = qlc:e(H),
7014                   false = lookup_keys(H) % doesn't handle this case
7015         end, [ordered_set], [{1,a},{2,b}])">>,
7016
7017    <<"etsc(fun(E) ->
7018                 I1 = 1, I2 = 1,
7019                 H = qlc:q([X || {X,_} <- ets:table(E),
7020                                 X =:= I1 orelse X == I2]),
7021                 [1] = qlc:e(H), % do not look up twice
7022                 [1] = lookup_keys(H)
7023         end, [ordered_set], [{1,a},{2,b}])">>,
7024
7025    <<"etsc(fun(E) ->
7026                 I1 = 1, I2 = 1, I3 = 1,
7027                 H = qlc:q([X || {X,_} <- ets:table(E),
7028                                 I1 == I2, I1 =:= I3, I3 == I2, I2 =:= I3,
7029                                 X =:= I1 orelse X == I2
7030                                 ]),
7031                 [1] = qlc:e(H),
7032                 [1] = lookup_keys(H)
7033         end, [ordered_set], [{1,a},{2,b}])">>,
7034
7035    <<"E = ets:new(join, [ordered_set]),
7036       true = ets:insert(E, [{1,a},{2,b,x},{3,c}]),
7037       Q = qlc:q([P || P <- ets:table(E),
7038                       P =:= {1,a} orelse P =:= {2,b,x}]),
7039       [{1,a},{2,b,x}] = qlc:e(Q),
7040       ets:delete(E)">>,
7041
7042    <<"etsc(fun(E) ->
7043                   Q = qlc:q([X || {X,Y} <- ets:table(E),
7044                                   ((X =:= 3) or (Y =:= 4))  and (X == a)]),
7045                   {list,{table,_},_} = i(Q),
7046                   [] = qlc:e(Q), % a is not an answer
7047                   [a] = lookup_keys(Q)
7048          end, [{keypos,1},ordered_set], [{a,3},{b,4}])">>,
7049
7050    <<"Q = qlc:q([{X,Y} ||
7051                  {X} <- [{<<3:4>>}],
7052                  {Y} <- [{<<3:4>>}],
7053                  X =:= <<1:3,1:1>>,        % <<3:4>>
7054                  Y =:= <<0:2,1:1,1:1>>,    % <<3:4>>
7055                  X =:= Y]),
7056                  [{<<3:4>>,<<3:4>>}] = qlc:e(Q)">>
7057
7058
7059    ],
7060
7061    run(Config, Ts).
7062
7063%% Syntax error.
7064otp_12946(Config) when is_list(Config) ->
7065    Text =
7066        <<"-export([init/0]).
7067           init() ->
7068               ok.
7069           y">>,
7070    {errors,[{4,erl_parse,_}],[]} = compile_file(Config, Text, []),
7071    ok.
7072
7073%% Examples from qlc(3).
7074manpage(Config) when is_list(Config) ->
7075    dets:start(),
7076    ok = compile_gb_table(Config),
7077
7078    Ts = [
7079       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7080          QC = qlc:cursor(QH),
7081          [{a,1}] = qlc:next_answers(QC, 1),
7082          [{a,2}] = qlc:next_answers(QC, 1),
7083          [{b,1},{b,2}] = qlc:next_answers(QC, all_remaining),
7084          ok = qlc:delete_cursor(QC)">>,
7085
7086       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7087          [{a,1},{a,2},{b,1},{b,2}] = qlc:eval(QH)">>,
7088
7089       <<"QH = [1,2,3,4,5,6],
7090          21 = qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH)">>,
7091
7092       <<"QH = qlc:q([{X,Y} || X <- [x,y], Y <- [a,b]]),
7093          B = \"begin\n\"
7094              \"    V1 =\n\"
7095              \"        qlc:q([ \n\"
7096              \"               SQV ||\n\"
7097              \"                   SQV <- [x,y]\n\"
7098              \"              ],\n\"
7099              \"              [{unique,true}]),\n\"
7100              \"    V2 =\n\"
7101              \"        qlc:q([ \n\"
7102              \"               SQV ||\n\"
7103              \"                   SQV <- [a,b]\n\"
7104              \"              ],\n\"
7105              \"              [{unique,true}]),\n\"
7106              \"    qlc:q([ \n\"
7107              \"           {X,Y} ||\n\"
7108              \"               X <- V1,\n\"
7109              \"               Y <- V2\n\"
7110              \"          ],\n\"
7111              \"          [{unique,true}])\n\"
7112              \"end\",
7113          true = B =:= qlc:info(QH, unique_all)">>,
7114
7115       <<"E1 = ets:new(e1, []),
7116          E2 = ets:new(e2, []),
7117          true = ets:insert(E1, [{1,a},{2,b}]),
7118          true = ets:insert(E2, [{a,1},{b,2}]),
7119          Q = qlc:q([{X,Z,W} ||
7120                        {X, Z} <- ets:table(E1),
7121                        {W, Y} <- ets:table(E2),
7122                        X =:= Y]),
7123          L = \"begin\n\"
7124              \"    V1 =\n\"
7125              \"        qlc:q([ \n\"
7126              \"               P0 ||\n\"
7127              \"                   P0 = {W,Y} <- ets:table(_)\n\"
7128              \"              ]),\n\"
7129              \"    V2 =\n\"
7130              \"        qlc:q([ \n\"
7131              \"               [G1|G2] ||\n\"
7132              \"                   G2 <- V1,\n\"
7133              \"                   G1 <- ets:table(_),\n\"
7134              \"                   element(2, G1) =:= element(1, G2)\n\"
7135              \"              ],\n\"
7136              \"              [{join,lookup}]),\n\"
7137              \"    qlc:q([ \n\"
7138              \"           {X,Z,W} ||\n\"
7139              \"               [{X,Z}|{W,Y}] <- V2\n\"
7140              \"          ])\n\"
7141              \"end\",
7142          Info1 =
7143             re:replace(qlc:info(Q),
7144                        \"table\\\\(#Ref<[\\.0-9]*>\",
7145                        \"table(_\", [{return,list},global]),
7146          F = fun(C) -> C =/= $\n andalso C =/= $\s end,
7147          Info = lists:filter(F, Info1),
7148          L1 = lists:filter(F, L),
7149          L1 = Info,
7150          ets:delete(E1),
7151          ets:delete(E2)">>,
7152
7153       <<"Q = qlc:q([{A,X,Z,W} ||
7154                        A <- [a,b,c],
7155                        {X,Z} <- [{a,1},{b,4},{c,6}],
7156                        {W,Y} <- [{2,a},{3,b},{4,c}],
7157                        X =:= Y],
7158                    {cache, list}),
7159          L =
7160       \"begin\n\"
7161       \"    V1 =\n\"
7162       \"        qlc:q([ \n\"
7163       \"               P0 ||\n\"
7164       \"                   P0 = {X,Z} <- qlc:keysort(1, [{a,1},{b,4},{c,6}], [])\n\"
7165       \"              ]),\n\"
7166       \"    V2 =\n\"
7167       \"        qlc:q([ \n\"
7168       \"               P0 ||\n\"
7169       \"                   P0 = {W,Y} <- qlc:keysort(2, [{2,a},{3,b},{4,c}], [])\n\"
7170       \"              ]),\n\"
7171       \"    V3 =\n\"
7172       \"        qlc:q([ \n\"
7173       \"               [G1|G2] ||\n\"
7174       \"                   G1 <- V1,\n\"
7175       \"                   G2 <- V2,\n\"
7176       \"                   element(1, G1) == element(2, G2)\n\"
7177       \"              ],\n\"
7178       \"              [{join,merge},{cache,list}]),\n\"
7179       \"    qlc:q([ \n\"
7180       \"           {A,X,Z,W} ||\n\"
7181       \"               A <- [a,b,c],\n\"
7182       \"               [{X,Z}|{W,Y}] <- V3,\n\"
7183       \"               X =:= Y\n\"
7184       \"          ])\n\"
7185       \"end\",
7186          L = qlc:info(Q)">>,
7187
7188       <<"E1 = ets:new(t, [set]), % uses =:=/2
7189          Q1 = qlc:q([K ||
7190          {K} <- ets:table(E1),
7191          K == 2.71 orelse K == a]),
7192          {list,{table,_}, [{{'$1'},[],['$1']}]} = i(Q1),
7193          true = ets:delete(E1)">>,
7194
7195       <<"F = fun(E, I) ->
7196                    qlc:q([V || {K,V} <- ets:table(E), K == I])
7197              end,
7198          E2 = ets:new(t, [set]),
7199          true = ets:insert(E2, [{{2,2},a},{{2,2.0},b},{{2.0,2},c}]),
7200          Q2 = F(E2, {2,2}),
7201          {table,{ets,table,[_,
7202                [{traverse,{select,[{{'$1','$2'},
7203                                     [{'==','$1',{const,{2,2}}}],
7204                                     ['$2']}]}}]]}} = i(Q2),
7205          [a,b,c] = lists:sort(qlc:e(Q2)),
7206          true = ets:delete(E2),
7207
7208          E3 = ets:new(t, [ordered_set]), % uses ==/2
7209          true = ets:insert(E3, [{{2,2.0},b}]),
7210          Q3 = F(E3,{2,2}),
7211          {list,{table,_},[{{'$1','$2'},[],['$2']}]} = i(Q3),
7212          [b] = qlc:e(Q3),
7213          true = ets:delete(E3)">>,
7214
7215       <<"T = gb_trees:empty(),
7216          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
7217                           ((X == 1) or (X == 2)) andalso
7218                           ((Y == a) or (Y == b) or (Y == c))]),
7219          L = \"ets:match_spec_run(lists:flatmap(fun(K) ->
7220                                        case
7221                                            gb_trees:lookup(K,
7222                                                            gb_trees:from_orddict([]))
7223                                        of
7224                                            {value,V} ->
7225                                                [{K,V}];
7226                                            none ->
7227                                                []
7228                                        end
7229                                 end,
7230                                 [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
7231                   ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))\",
7232          L = qlc:info(QH)">>
7233      ],
7234    run(Config, Ts),
7235
7236    L = [1,2,3],
7237    Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
7238    QH = qlc:string_to_handle("[X+1 || X <- L].", [], Bs),
7239    [2,3,4] = qlc:eval(QH),
7240
7241    %% ets(3)
7242    MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
7243    ETs = [
7244        [<<"true = ets:insert(Tab = ets:new(t, []),[{1,a},{2,b},{3,c},{4,d}]),
7245            MS = ">>, io_lib:format("~w", [MS]), <<",
7246            QH1 = ets:table(Tab, [{traverse, {select, MS}}]),
7247
7248            QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Tab), (X > 1) or (X < 5)]),
7249
7250            true = qlc:info(QH1) =:= qlc:info(QH2),
7251            true = ets:delete(Tab)">>]],
7252    run(Config, ETs),
7253
7254    %% dets(3)
7255    DTs = [
7256        [<<"{ok, T} = dets:open_file(t, []),
7257            ok = dets:insert(T, [{1,a},{2,b},{3,c},{4,d}]),
7258            MS = ">>, io_lib:format("~w", [MS]), <<",
7259            QH1 = dets:table(T, [{traverse, {select, MS}}]),
7260
7261            QH2 = qlc:q([{Y} || {X,Y} <- dets:table(t), (X > 1) or (X < 5)]),
7262
7263            true = qlc:info(QH1) =:= qlc:info(QH2),
7264            ok = dets:close(T)">>]],
7265    run(Config, DTs),
7266
7267    ok.
7268
7269compile_gb_table(Config) ->
7270    GB_table_file = filename("gb_table.erl", Config),
7271    ok = file:write_file(GB_table_file, gb_table()),
7272    {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
7273    code:purge(gb_table),
7274    {module, gb_table} =
7275        code:load_abs(filename:rootname(GB_table_file)),
7276    ok.
7277
7278gb_table() ->
7279    <<"
7280-module(gb_table).
7281
7282-export([table/1]).
7283
7284table(T) ->
7285    TF = fun() -> qlc_next(gb_trees:next(gb_trees:iterator(T))) end,
7286    InfoFun = fun(num_of_objects) -> gb_trees:size(T);
7287                 (keypos) -> 1;
7288                 (is_sorted_key) -> true;
7289                 (is_unique_objects) -> true;
7290                 (_) -> undefined
7291              end,
7292    LookupFun =
7293        fun(1, Ks) ->
7294                lists:flatmap(fun(K) ->
7295                                      case gb_trees:lookup(K, T) of
7296                                          {value, V} -> [{K,V}];
7297                                          none -> []
7298                                      end
7299                              end, Ks)
7300        end,
7301    FormatFun =
7302        fun({all, NElements, ElementFun}) ->
7303                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7304                                      [gb_nodes(T, NElements, ElementFun)]),
7305                io_lib:format(\"gb_table:table(~s)\", [ValsS]);
7306           ({lookup, 1, KeyValues, _NElements, ElementFun}) ->
7307                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7308                                      [gb_nodes(T, infinity, ElementFun)]),
7309                io_lib:format(\"lists:flatmap(fun(K) -> \"
7310                              \"case gb_trees:lookup(K, ~s) of \"
7311                              \"{value, V} -> [{K,V}];none -> [] end \"
7312                              \"end, ~w)\",
7313                              [ValsS, [ElementFun(KV) || KV <- KeyValues]])
7314        end,
7315    qlc:table(TF, [{info_fun, InfoFun}, {format_fun, FormatFun},
7316                   {lookup_fun, LookupFun},{key_equality,'=='}]).
7317
7318qlc_next({X, V, S}) ->
7319    [{X,V} | fun() -> qlc_next(gb_trees:next(S)) end];
7320qlc_next(none) ->
7321    [].
7322
7323gb_nodes(T, infinity, ElementFun) ->
7324    gb_nodes(T, -1, ElementFun);
7325gb_nodes(T, NElements, ElementFun) ->
7326    gb_iter(gb_trees:iterator(T), NElements, ElementFun).
7327
7328gb_iter(_I, 0, _EFun) ->
7329    '...';
7330gb_iter(I0, N, EFun) ->
7331    case gb_trees:next(I0) of
7332        {X, V, I} ->
7333            [EFun({X,V}) | gb_iter(I, N-1, EFun)];
7334        none ->
7335            []
7336    end.
7337    ">>.
7338
7339
7340%% OTP-6674. Join info and extra constants.
7341backward(Config) when is_list(Config) ->
7342    try_old_join_info(Config),
7343    ok.
7344
7345try_old_join_info(Config) ->
7346    %% Check join info for handlers of extra constants.
7347    File = filename:join(?datadir, "join_info_compat.erl"),
7348    M = join_info_compat,
7349    {ok, M} = compile:file(File, [{outdir, ?datadir}]),
7350    {module, M} = code:load_abs(filename:rootname(File)),
7351    H = M:create_handle(),
7352    A0 = erl_anno:new(0),
7353    {block,A0,
7354     [{match,_,_,
7355       {call,_,_,
7356        [{lc,_,_,
7357          [_,
7358           {op,_,'=:=',
7359            {float,_,192.0},
7360            {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}},
7361      _,_,
7362      {call,_,_,
7363       [{lc,_,_,
7364         [_,
7365          {op,_,'=:=',{var,_,'B'},{float,_,192.0}},
7366          {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]}
7367        = qlc:info(H,{format,abstract_code}),
7368    [{1,1},{2,2}] = qlc:e(H),
7369
7370    H2 = M:lookup_handle(),
7371    {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} =
7372        qlc:info(H2, {format,debug}),
7373    [{1,1},{2,2}] = qlc:e(H2).
7374
7375forward(Config) when is_list(Config) ->
7376    Ts = [
7377      %% LC_fun() returns something unknown.
7378      <<"FakeH = {qlc_handle,{qlc_lc,fun() -> {foo,bar} end,
7379                             {qlc_opt,false,false,-1,any,[],any,524288}}},
7380         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7381
7382%% 'f1' should be used for new stuff that does not interfer with old behavior
7383%%       %% The unused element 'f1' of #qlc_table seems to be used.
7384%%       <<"DF = fun() -> foo end,
7385%%          FakeH = {qlc_handle,{qlc_table,DF,
7386%%                        true,DF,DF,DF,DF,DF,
7387%%                        undefined,not_undefined,undefined,no_match_spec}},
7388%%          {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7389
7390      %% #qlc_opt has changed.
7391      <<"H = qlc:q([X || X <- []]),
7392         {qlc_handle, {qlc_lc, Fun, _Opt}} = H,
7393         FakeH = {qlc_handle, {qlc_lc, Fun, {new_qlc_opt, a,b,c}}},
7394         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>
7395
7396     ],
7397    run(Config, Ts),
7398    ok.
7399
7400eep37(Config) when is_list(Config) ->
7401    Ts = [
7402        <<"H = (fun _Handle() -> qlc:q([X || X <- []]) end)(),
7403           [] = qlc:eval(H)">>
7404    ],
7405    run(Config, Ts),
7406    ok.
7407
7408%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7409
7410bad_table_throw(Tab) ->
7411    Limit = 1,
7412    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7413    PreFun = fun(_) -> throw({throw,bad_pre_fun}) end,
7414    PostFun = fun() -> throw({throw,bad_post_fun}) end,
7415    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7416    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7417                       {info_fun, InfoFun}]).
7418
7419bad_table_exit(Tab) ->
7420    Limit = 1,
7421    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7422    PreFun = fun(_) -> erlang:error(bad_pre_fun) end,
7423    PostFun = fun() -> erlang:error(bad_post_fun) end,
7424    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7425    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7426                       {info_fun, InfoFun}]).
7427
7428info(_Tab, is_unique_objects) ->
7429    false;
7430info(Tab, Tag) ->
7431    try ets:info(Tab, Tag) catch _:_ -> undefined end.
7432
7433create_ets(S, E) ->
7434    create_ets(lists:seq(S, E)).
7435
7436create_ets(L) ->
7437    E1 = ets:new(e, []),
7438    true = ets:insert(E1, [{X,X} || X <- L]),
7439    E1.
7440
7441etsc(F, Objs) ->
7442    etsc(F, [{keypos,1}], Objs).
7443
7444etsc(F, Opts, Objs) ->
7445    E = ets:new(test, Opts),
7446    true = ets:insert(E, Objs),
7447    V = F(E),
7448    ets:delete(E),
7449    V.
7450
7451join_info(H) ->
7452    {{qlc, S, Options}, Bs} = strip_qlc_call2(H),
7453    %% "Hide" the call to qlc_pt from the test in run_test().
7454    LoadedPT = code:is_loaded(qlc_pt),
7455    QH = qlc:string_to_handle(S, Options, Bs),
7456    _ = [unload_pt() || false <- [LoadedPT]], % doesn't take long...
7457    case {join_info_count(H), join_info_count(QH)} of
7458        {N, N} ->
7459            N;
7460        Ns ->
7461            Ns
7462    end.
7463
7464strip_qlc_call(H) ->
7465    {Expr, _Bs} = strip_qlc_call2(H),
7466    Expr.
7467
7468strip_qlc_call2(H) ->
7469    S = qlc:info(H, {flat, false}),
7470    {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]),
7471    {ok, [Expr], Bs} = erl_eval:extended_parse_exprs(Tokens),
7472    {case Expr of
7473         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} ->
7474             {qlc, lists:flatten([erl_pp:expr(LC), "."]), []};
7475         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC, Opts]} ->
7476             {qlc, lists:flatten([erl_pp:expr(LC), "."]),
7477              erl_parse:normalise(Opts)};
7478         {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} ->
7479             {match_spec, Expr};
7480         {call,_,{remote,_,{atom,_,M},{atom,_,table}},_} ->
7481             {table, M, Expr};
7482         _ ->
7483             []
7484     end, Bs}.
7485
7486-record(ji, {nmerge = 0, nlookup = 0, nnested_loop = 0, nkeysort = 0}).
7487
7488%% Counts join options and (all) calls to qlc:keysort().
7489join_info_count(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    #ji{nmerge = Nmerge, nlookup = Nlookup,
7494        nkeysort = NKeysort, nnested_loop = Nnested_loop} =
7495        ji(Expr, #ji{}),
7496    {Nmerge, Nlookup, Nnested_loop, NKeysort}.
7497
7498ji({call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC,Options]}, JI) ->
7499    NJI = case lists:keysearch(join, 1, erl_parse:normalise(Options)) of
7500              {value, {join, merge}} ->
7501                  JI#ji{nmerge = JI#ji.nmerge + 1};
7502              {value, {join, lookup}} ->
7503                  JI#ji{nlookup = JI#ji.nlookup + 1};
7504              {value, {join, nested_loop}} ->
7505                  JI#ji{nnested_loop = JI#ji.nnested_loop + 1};
7506              _  ->
7507                  JI
7508          end,
7509    ji(LC, NJI);
7510ji({call,_,{remote,_,{atom,_,qlc},{atom,_,keysort}},[_KP,H,_Options]}, JI) ->
7511    ji(H, JI#ji{nkeysort = JI#ji.nkeysort + 1});
7512ji(T, JI) when is_tuple(T) ->
7513    ji(tuple_to_list(T), JI);
7514ji([E | Es], JI) ->
7515    ji(Es, ji(E, JI));
7516ji(_, JI) ->
7517    JI.
7518
7519%% Designed for ETS' and gb_table's format funs.
7520lookup_keys(Q) ->
7521    case lists:flatten(lookup_keys(i(Q), [])) of
7522        [] -> false;
7523        L -> lists:usort(L)
7524    end.
7525
7526lookup_keys([Q | Qs], L) ->
7527    lookup_keys(Qs, lookup_keys(Q, L));
7528lookup_keys({qlc,_,Quals,_}, L) ->
7529    lookup_keys(Quals, L);
7530lookup_keys({list,Q,_}, L) ->
7531    lookup_keys(Q, L);
7532lookup_keys({generate,_,Q}, L) ->
7533    lookup_keys(Q, L);
7534lookup_keys({table,Chars}, L) when is_list(Chars) ->
7535    {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]),
7536    {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens),
7537    case Expr of
7538        {call,_,_,[_fun,AKs]} ->
7539            case erl_parse:normalise(AKs) of
7540                Ks when is_list(Ks) ->
7541                    [lists:sort(Ks) | L];
7542                K -> % assume keys are never lists (ets only)
7543                    [K | L]
7544            end;
7545        _ -> % gb_table
7546            L
7547    end;
7548lookup_keys(_Q, L) ->
7549    L.
7550
7551bad_table_format(Tab) ->
7552    Limit = 1,
7553    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7554    FormatFun = {is, no, good},
7555    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7556
7557bad_table_format_arity(Tab) ->
7558    Limit = 1,
7559    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7560    FormatFun = fun() -> {?MODULE, bad_table_format_arity, [Tab]} end,
7561    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7562
7563bad_table_traverse(Tab) ->
7564    Limit = 1,
7565    Select = fun(MS, _) -> cb(ets:select(Tab, MS, Limit)) end,
7566    qlc:table(Select, []).
7567
7568bad_table_post(Tab) ->
7569    Limit = 1,
7570    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7571    qlc:table(SelectFun, [{pre_fun,undefined},
7572                          {post_fun, fun(X) -> X end},
7573                          {info_fun, undefined}]).
7574
7575bad_table_lookup(Tab) ->
7576    Limit = 1,
7577    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7578    qlc:table(SelectFun, {lookup_fun, fun(X) -> X end}).
7579
7580bad_table_max_lookup(Tab) ->
7581    Limit = 1,
7582    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7583    qlc:table(SelectFun, {max_lookup, -2}).
7584
7585bad_table_info_arity(Tab) ->
7586    Limit = 1,
7587    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7588    InfoFun = fun() -> {?MODULE, bad_table_info_arity, [Tab]} end,
7589    qlc:table(SelectFun, [{info_fun, InfoFun}]).
7590
7591default_table(Tab) ->
7592    Limit = 1,
7593    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7594    qlc:table(SelectFun, [{format_fun, undefined},
7595                          {info_fun, undefined},
7596                          {lookup_fun, undefined},
7597                          {parent_fun, undefined},
7598                          {pre_fun,undefined},
7599                          {post_fun, undefined}]).
7600
7601bad_table(Tab) ->
7602    Limit = 1,
7603    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7604    qlc:table(SelectFun, [{info, fun() -> ok end}]).
7605
7606bad_table_info_fun_n_objects(Tab) ->
7607    Limit = 1,
7608    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7609    LookupFun = fun(_Pos, Ks) ->
7610                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7611                end,
7612    InfoFun = fun(num_of_objects) -> exit(finito);
7613                 (_) -> undefined
7614              end,
7615    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7616
7617bad_table_info_fun_indices(Tab) ->
7618    Limit = 1,
7619    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7620    LookupFun = fun(_Pos, Ks) ->
7621                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7622                end,
7623    InfoFun = fun(indices) -> throw({throw,apa});
7624                 (_) -> undefined
7625              end,
7626    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7627
7628bad_table_info_fun_keypos(Tab) ->
7629    Limit = 1,
7630    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7631    LookupFun = fun(_Pos, Ks) ->
7632                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7633                end,
7634    InfoFun = fun(indices) -> erlang:error(keypos);
7635                  (_) -> undefined
7636              end,
7637    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7638
7639bad_table_key_equality(Tab) ->
7640    Limit = 1,
7641    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7642    LookupFun = fun(_Pos, Ks) ->
7643                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7644                end,
7645    qlc:table(SelectFun, [{lookup_fun, LookupFun},{key_equality,'=/='}]).
7646
7647cb('$end_of_table') ->
7648    [];
7649cb({Objects,Cont}) ->
7650    Objects ++ fun() -> cb(ets:select(Cont)) end.
7651
7652i(H) ->
7653    i(H, []).
7654
7655i(H, Options) when is_list(Options) ->
7656    case has_format(Options) of
7657        true -> qlc:info(H, Options);
7658        false -> qlc:info(H, [{format, debug} | Options])
7659    end;
7660i(H, Option) ->
7661    i(H, [Option]).
7662
7663has_format({format,_}) ->
7664    true;
7665has_format([E | Es]) ->
7666    has_format(E) or has_format(Es);
7667has_format(_) ->
7668    false.
7669
7670format_info(H, Flat) ->
7671    L = qlc:info(H, [{flat, Flat}, {format,string}]),
7672    re:replace(L, "\s|\n|\t|\f|\r|\v", "", [{return,list},global]).
7673
7674%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7675%% A list turned into a table...
7676
7677table_kill_parent(List, Indices) ->
7678    ParentFun = fun() -> exit(self(), kill) end,
7679    table_i(List, Indices, ParentFun).
7680
7681table_parent_throws(List, Indices) ->
7682    ParentFun = fun() -> throw({throw,thrown}) end,
7683    table_i(List, Indices, ParentFun).
7684
7685table_parent_exits(List, Indices) ->
7686    ParentFun = fun() -> 1 + Indices end,
7687    table_i(List, Indices, ParentFun).
7688
7689table_bad_parent_fun(List, Indices) ->
7690    ParentFun = fun(X) -> X end, % parent_fun should be nullary
7691    table_i(List, Indices, ParentFun).
7692
7693table(List, Indices) ->
7694    ParentFun = fun() -> self() end,
7695    table_i(List, Indices, ParentFun).
7696
7697table(List, KeyPos, Indices) ->
7698    ParentFun = fun() -> self() end,
7699    table(List, Indices, KeyPos, ParentFun).
7700
7701table_i(List, Indices, ParentFun) ->
7702    table(List, Indices, undefined, ParentFun).
7703
7704table(List, Indices, KeyPos, ParentFun) ->
7705    TraverseFun = fun() -> list_traverse(List) end,
7706    PreFun = fun(PreArgs) ->
7707                     {value, {parent_value, Pid}} =
7708                         lists:keysearch(parent_value, 1, PreArgs),
7709                     true = is_pid(Pid)
7710             end,
7711    PostFun = fun() -> ok end,
7712    InfoFun = fun(indices) ->
7713                      Indices;
7714                 (is_unique_objects) ->
7715                      undefined;
7716                 (keypos) ->
7717                      KeyPos;
7718                 (num_of_objects) ->
7719                      undefined;
7720                 (_) ->
7721                      undefined
7722              end,
7723    LookupFun =
7724        fun(Column, Values) ->
7725                lists:flatmap(fun(V) ->
7726                                      case lists:keysearch(V, Column, List) of
7727                                          false -> [];
7728                                          {value,Val} -> [Val]
7729                                      end
7730                              end, Values)
7731
7732                end,
7733    FormatFun = fun(all) ->
7734                        L = erl_anno:new(17),
7735                        {call,L,{remote,L,{atom,L,?MODULE},{atom,L,the_list}},
7736                                 [erl_parse:abstract(List, 17)]};
7737                   ({lookup, Column, Values}) ->
7738                        {?MODULE, list_keys, [Values, Column, List]}
7739                end,
7740    qlc:table(TraverseFun, [{info_fun,InfoFun}, {pre_fun, PreFun},
7741                            {post_fun, PostFun}, {lookup_fun, LookupFun},
7742                            {format_fun, FormatFun},
7743                            {parent_fun, ParentFun}]).
7744
7745stop_list(List, Ets) ->
7746    Traverse = fun() -> list_traverse(List) end,
7747    PV = a_sample_parent_value,
7748    ParentFun = fun() -> PV end,
7749    Pre = fun(PreArgs) ->
7750                  {value, {parent_value, PV}} =
7751                      lists:keysearch(parent_value, 1, PreArgs),
7752                  {value, {stop_fun, Fun}} =
7753                      lists:keysearch(stop_fun, 1, PreArgs),
7754                  true = ets:insert(Ets, {stop_fun, Fun})
7755          end,
7756    qlc:table(Traverse, [{pre_fun, Pre}, {parent_fun, ParentFun}]).
7757
7758list_traverse([]) ->
7759    [];
7760list_traverse([E | Es]) ->
7761    [E | fun() -> list_traverse(Es) end].
7762
7763table_error(List, Error) ->
7764    table_error(List, undefined, Error).
7765
7766table_error(List, KeyPos, Error) ->
7767    TraverseFun = fun() -> list_traverse2(lists:sort(List), Error) end,
7768    InfoFun = fun(is_sorted_key) -> true;
7769                 (keypos) -> KeyPos;
7770                 (_) -> undefined
7771              end,
7772    qlc:table(TraverseFun, [{info_fun,InfoFun}]).
7773
7774list_traverse2([], Err) ->
7775    Err;
7776list_traverse2([E | Es], Err) ->
7777    [E | fun() -> list_traverse2(Es, Err) end].
7778
7779table_lookup_error(List) ->
7780    TraverseFun = fun() -> list_traverse(List) end,
7781    LookupFun = fun(_Column, _Values) -> {error,lookup,failed} end,
7782    InfoFun = fun(keypos) -> 1;
7783                 (_) -> undefined
7784              end,
7785    qlc:table(TraverseFun, [{lookup_fun,LookupFun},{info_fun,InfoFun}]).
7786
7787prep_scratchdir(Dir) ->
7788    put('$qlc_tmpdir', true),
7789    _ = filelib:ensure_dir(Dir),
7790    lists:foreach(fun(F) -> file:delete(F)
7791                  end, filelib:wildcard(filename:join(Dir, "*"))),
7792    true.
7793
7794%% Truncate just once.
7795truncate_tmpfile(Dir, Where) ->
7796    case get('$qlc_tmpdir') of
7797        true ->
7798            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7799            TmpFile = filename:join(Dir, TmpFile0),
7800            truncate(TmpFile, Where),
7801            erase('$qlc_tmpdir');
7802        _ ->
7803            true
7804    end.
7805
7806truncate(File, Where) ->
7807    {ok, Fd} = file:open(File, [read, write]),
7808    {ok, _} = file:position(Fd, Where),
7809    ok = file:truncate(Fd),
7810    ok = file:close(Fd).
7811
7812%% Crash just once.
7813crash_tmpfile(Dir, Where) ->
7814    case get('$qlc_tmpdir') of
7815        true ->
7816            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7817            TmpFile = filename:join(Dir, TmpFile0),
7818            crash(TmpFile, Where),
7819            erase('$qlc_tmpdir');
7820        _ ->
7821            true
7822    end.
7823
7824crash(File, Where) ->
7825    {ok, Fd} = file:open(File, [read, write]),
7826    {ok, _} = file:position(Fd, Where),
7827    ok = file:write(Fd, [10]),
7828    ok = file:close(Fd).
7829
7830%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7831
7832run(Config, Tests) ->
7833    run(Config, [], Tests).
7834
7835run(Config, Extra, Tests) ->
7836    lists:foreach(fun(Body) -> run_test(Config, Extra, Body) end, Tests).
7837
7838run_test(Config, Extra, {cres, Body, ExpectedCompileReturn}) ->
7839    run_test(Config, Extra, {cres, Body, _Opts = [], ExpectedCompileReturn});
7840run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
7841    {SourceFile, Mod} = compile_file_mod(Config),
7842    P = [Extra,<<"function() -> ">>, Body, <<", ok. ">>],
7843    CompileReturn = compile_file(Config, P, Opts),
7844    case comp_compare(ExpectedCompileReturn, CompileReturn) of
7845        true -> ok;
7846        false -> expected(ExpectedCompileReturn, CompileReturn, SourceFile)
7847    end,
7848    AbsFile = filename:rootname(SourceFile, ".erl"),
7849    _ = code:purge(Mod),
7850    {module, _} = code:load_abs(AbsFile, Mod),
7851
7852    Ms0 = erlang:process_info(self(),messages),
7853    Before = {{lget(), lists:sort(ets:all()), Ms0}, pps()},
7854
7855    %% Prepare the check that the qlc module does not call qlc_pt.
7856    _ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)],
7857                        Name =/= cover_compiled],
7858
7859    R = case catch Mod:function() of
7860            {'EXIT', _Reason} = Error ->
7861                io:format("failed, got ~p~n", [Error]),
7862                fail(SourceFile);
7863            Reply ->
7864                Reply
7865        end,
7866
7867    %% Check that the qlc module does not call qlc_pt:
7868    case code:is_loaded(qlc_pt) of
7869        {file, cover_compiled} ->
7870            ok;
7871        {file, _} ->
7872            io:format("qlc_pt was loaded in runtime~n", []),
7873            fail(SourceFile);
7874        false ->
7875            ok
7876    end,
7877
7878    wait_for_expected(R, Before, SourceFile, true),
7879    code:purge(Mod);
7880run_test(Config, Extra, Body) ->
7881    run_test(Config, Extra, {cres,Body,[]}).
7882
7883wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) ->
7884    Ms = erlang:process_info(self(),messages),
7885    After = {_,PPS1} = {{lget(), lists:sort(ets:all()), Ms}, pps()},
7886    case {R, After} of
7887        {ok, Before} ->
7888            ok;
7889        {ok, {Strict0,_}} ->
7890            {Ports0,Procs0} = PPS0,
7891            {Ports1,Procs1} = PPS1,
7892            case {Ports1 -- Ports0, Procs1 -- Procs0} of
7893                {[], []} -> ok;
7894                _ when Wait ->
7895                    timer:sleep(1000),
7896                    wait_for_expected(R, Before, SourceFile, false);
7897                {PortsDiff,ProcsDiff} ->
7898                    io:format("failure, got ~p~n, expected ~p\n",
7899                              [PPS1, PPS0]),
7900                    show("Old port", Ports0 -- Ports1),
7901                    show("New port", PortsDiff),
7902                    show("Old proc", Procs0 -- Procs1),
7903                    show("New proc", ProcsDiff),
7904                    fail(SourceFile)
7905            end;
7906        _ when Wait ->
7907            timer:sleep(1000),
7908            wait_for_expected(R, Before, SourceFile, false);
7909        _ ->
7910            expected({ok,Before}, {R,After}, SourceFile)
7911    end.
7912
7913%% The qlc modules uses the process dictionary for storing names of files.
7914lget() ->
7915    lists:sort([T || {K, _} = T <- get(), is_qlc_key(K)]).
7916
7917%% Copied from the qlc module.
7918-define(LCACHE_FILE(Ref), {Ref, '$_qlc_cache_tmpfiles_'}).
7919-define(MERGE_JOIN_FILE, '$_qlc_merge_join_tmpfiles_').
7920
7921is_qlc_key(?LCACHE_FILE(_)) -> true;
7922is_qlc_key(?MERGE_JOIN_FILE) -> true;
7923is_qlc_key(_) -> false.
7924
7925unload_pt() ->
7926    erlang:garbage_collect(), % get rid of references to qlc_pt...
7927    _ = code:purge(qlc_pt),
7928    _ = code:delete(qlc_pt).
7929
7930compile_format(Config, Tests) ->
7931    Fun = fun(Test, Opts) ->
7932                  Return = compile_file(Config, Test, Opts),
7933                  format_messages(Return)
7934          end,
7935    compile(Config, Tests, Fun).
7936
7937format_messages({warnings,Ws}) ->
7938    format_messages({errors,[],Ws});
7939format_messages({errors,Es,Ws}) ->
7940    {[format_msg(E, Mod) || {_Line,Mod,E} <- Es],
7941     [format_msg(W, Mod) || {_Line,Mod,W} <- Ws]}.
7942
7943format_msg(Msg, Mod) ->
7944    IOlist = Mod:format_error(Msg),
7945    binary_to_list(iolist_to_binary(IOlist)).
7946
7947compile(Config, Tests) ->
7948    Fun = fun(Test, Opts) -> catch compile_file(Config, Test, Opts) end,
7949    compile(Config, Tests, Fun).
7950
7951compile(Config, Tests, Fun) ->
7952    F = fun({TestName,Test,Opts,Expected}, BadL) ->
7953                Return = Fun(Test, Opts),
7954                case comp_compare(Expected, Return) of
7955                    true ->
7956                        BadL;
7957                    false ->
7958                        {File, _Mod} = compile_file_mod(Config),
7959                        expected(TestName, Expected, Return, File)
7960                end
7961        end,
7962    lists:foldl(F, [], Tests).
7963
7964%% Compiles a test module and returns the list of errors and warnings.
7965
7966compile_file(Config, Test0, Opts0) ->
7967    {File, Mod} = compile_file_mod(Config),
7968    Test = list_to_binary(["-module(", atom_to_list(Mod), "). "
7969                           "-import(qlc_SUITE, [i/1,i/2,format_info/2]). "
7970                           "-import(qlc_SUITE, [etsc/2, etsc/3]). "
7971                           "-import(qlc_SUITE, [create_ets/2]). "
7972                           "-import(qlc_SUITE, [strip_qlc_call/1]). "
7973                           "-import(qlc_SUITE, [join_info/1]). "
7974                           "-import(qlc_SUITE, [join_info_count/1]). "
7975                           "-import(qlc_SUITE, [lookup_keys/1]). "
7976                           "-include_lib(\"stdlib/include/qlc.hrl\"). ",
7977                           Test0]),
7978    Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0],
7979    ok = file:write_file(File, Test),
7980    case compile:file(File, Opts) of
7981        {ok, _M, Ws} -> warnings(File, Ws);
7982        {error, [{File,Es}], []} -> {errors, Es, []};
7983        {error, [{File,Es}], [{File,Ws}]} -> {errors, Es, Ws}
7984    end.
7985
7986comp_compare(T, T) ->
7987    true;
7988comp_compare(T1, T2_0) ->
7989    T2 = wskip(T2_0),
7990    T1 =:= T2
7991       %% This clause should eventually be removed.
7992       orelse ln(T1) =:= T2 orelse T1 =:= ln(T2).
7993
7994wskip([]) ->
7995    [];
7996wskip([{_,sys_core_fold,{eval_failure,badarg}}|L]) ->
7997    wskip(L);
7998wskip([{{L,_C},sys_core_fold,M}|L]) ->
7999    [{L,sys_core_fold,M}|wskip(L)];
8000wskip({T,L}) ->
8001    {T,wskip(L)};
8002wskip([M|L]) ->
8003    [M|wskip(L)];
8004wskip(T) ->
8005    T.
8006
8007%% Replaces locations like {Line,Column} with Line.
8008ln({warnings,L}) ->
8009    {warnings,ln0(L)};
8010ln({errors,EL,WL}) ->
8011    {errors,ln0(EL),ln0(WL)};
8012ln(L) ->
8013    ln0(L).
8014
8015ln0(L) ->
8016    lists:sort(ln1(L)).
8017
8018ln1([]) ->
8019    [];
8020ln1([{File,Ms}|MsL]) when is_list(File) ->
8021    [{File,ln0(Ms)}|ln1(MsL)];
8022ln1([{{L,_C},Mod,Mess0}|Ms]) ->
8023    Mess = case Mess0 of
8024               {exported_var,V,{Where,{L1,_C1}}} ->
8025                   {exported_var,V,{Where,L1}};
8026               {unsafe_var,V,{Where,{L1,_C1}}} ->
8027                   {unsafe_var,V,{Where,L1}};
8028               %% There are more...
8029               M ->
8030                   M
8031           end,
8032    [{L,Mod,Mess}|ln1(Ms)];
8033ln1([M|Ms]) ->
8034    [M|ln1(Ms)].
8035
8036%% -> {FileName, Module}; {string(), atom()}
8037compile_file_mod(Config) ->
8038    NameL = lists:concat([?TESTMODULE, "_", ?testcase]),
8039    Name = list_to_atom(NameL),
8040    File = filename(NameL ++ ".erl", Config),
8041    {File, Name}.
8042
8043filename(Name, Config) when is_atom(Name) ->
8044    filename(atom_to_list(Name), Config);
8045filename(Name, Config) ->
8046    filename:join(?privdir, Name).
8047
8048show(_S, []) ->
8049    ok;
8050show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
8051    io:format("~s: ~w (~w), ~w: ~p~n",
8052              [S, Pid, proc_reg_name(Name), InitCall,
8053               erlang:process_info(Pid)]),
8054    show(S, Pids);
8055show(S, [{Port, _}|Ports]) when is_port(Port)->
8056    io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
8057    show(S, Ports).
8058
8059pps() ->
8060    {port_list(), process_list()}.
8061
8062port_list() ->
8063    [{P,safe_second_element(erlang:port_info(P, name))} ||
8064        P <- erlang:ports()].
8065
8066process_list() ->
8067    [{P,process_info(P, registered_name),
8068      safe_second_element(process_info(P, initial_call))} ||
8069        P <- processes(), is_process_alive(P)].
8070
8071proc_reg_name({registered_name, Name}) -> Name;
8072proc_reg_name([]) -> no_reg_name.
8073
8074safe_second_element({_,Info}) -> Info;
8075safe_second_element(Other) -> Other.
8076
8077warnings(File, Ws) ->
8078    case lists:append([W || {F, W} <- Ws, F =:= File]) of
8079        [] -> [];
8080        L -> {warnings, L}
8081    end.
8082
8083expected(Test, Expected, Got, File) ->
8084    io:format("~nTest ~p failed. ", [Test]),
8085    expected(Expected, Got, File).
8086
8087expected(Expected, Got, File) ->
8088    io:format("Expected~n  ~p~n, but got~n  ~p~n", [Expected, Got]),
8089    fail(File).
8090
8091fail(Source) ->
8092    ct:fail({failed,testcase,on,Source}).
8093
8094%% Copied from global_SUITE.erl.
8095
8096install_error_logger() ->
8097    error_logger:add_report_handler(?MODULE, self()).
8098
8099uninstall_error_logger() ->
8100    error_logger:delete_report_handler(?MODULE).
8101
8102read_error_logger() ->
8103    receive
8104	{error, Why} ->
8105            {error, Why};
8106        {info, Why} ->
8107            {info, Why};
8108        {warning, Why} ->
8109            {warning, Why};
8110        {error, Pid, Tuple} ->
8111            {error, Pid, Tuple}
8112    after 1000 ->
8113	    io:format("No reply after 1 s\n", []),
8114	    ct:fail(failed)
8115    end.
8116
8117%%-----------------------------------------------------------------
8118%% The error_logger handler used.
8119%% (Copied from stdlib/test/proc_lib_SUITE.erl.)
8120%%-----------------------------------------------------------------
8121init(Tester) ->
8122    {ok, Tester}.
8123
8124handle_event({error, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8125    Tester ! {error, Why},
8126    {ok, Tester};
8127handle_event({error, _GL, {_Pid, _Msg, [P, T]}}, Tester) when is_pid(P) ->
8128    Tester ! {error, P, T},
8129    {ok, Tester};
8130handle_event({info_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) ->
8131    Tester ! {info, Why},
8132    {ok, Tester};
8133handle_event({warning_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8134    Tester ! {warning, Why},
8135    {ok, Tester};
8136handle_event(_Event, State) ->
8137    {ok, State}.
8138
8139handle_info(_, State) ->
8140    {ok, State}.
8141
8142handle_call(_Query, State) -> {ok, {error, bad_query}, State}.
8143
8144terminate(_Reason, State) ->
8145    State.
8146