aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/qlc_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/qlc_SUITE.erl')
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl613
1 files changed, 240 insertions, 373 deletions
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 6f94e740eb..75971bcf11 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -25,7 +25,7 @@
-define(QLC, qlc).
-define(QLCs, "qlc").
-%-define(debug, true).
+%%-define(debug, true).
%% There are often many tests per testcase. Most tests are copied to a
%% module, a file. The file is compiled and the test run. Should the
@@ -44,9 +44,9 @@
-define(t, test_server).
-else.
-include_lib("common_test/include/ct.hrl").
--define(datadir, ?config(data_dir, Config)).
--define(privdir, ?config(priv_dir, Config)).
--define(testcase, ?config(?TESTCASE, Config)).
+-define(datadir, proplists:get_value(data_dir, Config)).
+-define(privdir, proplists:get_value(priv_dir, Config)).
+-define(testcase, proplists:get_value(?TESTCASE, Config)).
-endif.
-include_lib("stdlib/include/ms_transform.hrl").
@@ -80,7 +80,7 @@
backward/1, forward/1,
- eep37/1]).
+ eep37/1]).
%% Internal exports.
-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
@@ -107,19 +107,15 @@
handle_event/2, handle_call/2, handle_info/2,
terminate/2]).
-% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(5)).
-
init_per_testcase(Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
- [{?TESTCASE, Case}, {watchdog, Dog} | Config].
+ [{?TESTCASE, Case} | Config].
end_per_testcase(_Case, _Config) ->
- Dog = ?config(watchdog, _Config),
- test_server:timetrap_cancel(Dog),
ok.
-suite() -> [{ct_hooks,[ts_install_cth]}].
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,5}}].
all() ->
[{group, parse_transform}, {group, evaluation},
@@ -159,35 +155,30 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
-badarg(doc) ->
- "Badarg.";
-badarg(suite) -> [];
badarg(Config) when is_list(Config) ->
Ts =
- [{badarg,
- <<"-import(qlc, [q/1, q/2]).
+ [{badarg,
+ <<"-import(qlc, [q/1, q/2]).
q(_, _, _) -> ok.
- badarg() ->
- qlc:q(foo),
- qlc:q(foo, cache_all),
- qlc:q(foo, cache_all, extra),
- q(bar),
- q(bar, cache_all),
- q(bar, cache_all, extra).
- ">>,
+badarg() ->
+ qlc:q(foo),
+ qlc:q(foo, cache_all),
+ qlc:q(foo, cache_all, extra),
+ q(bar),
+ q(bar, cache_all),
+ q(bar, cache_all, extra).
+">>,
[],
- {errors,[{5,?QLC,not_a_query_list_comprehension},
- {6,?QLC,not_a_query_list_comprehension},
- {8,?QLC,not_a_query_list_comprehension},
- {9,?QLC,not_a_query_list_comprehension}],
- []}}],
- ?line [] = compile(Config, Ts),
+{errors,[{5,?QLC,not_a_query_list_comprehension},
+ {6,?QLC,not_a_query_list_comprehension},
+ {8,?QLC,not_a_query_list_comprehension},
+ {9,?QLC,not_a_query_list_comprehension}],
+ []}}],
+ [] = compile(Config, Ts),
ok.
-nested_qlc(doc) ->
- "Nested qlc expressions.";
-nested_qlc(suite) -> [];
+%% Nested qlc expressions.
nested_qlc(Config) when is_list(Config) ->
%% Nested QLC expressions. X is bound before the first one; Z and X
%% before the second one.
@@ -227,12 +218,10 @@ nested_qlc(Config) when is_list(Config) ->
[warn_unused_vars],
{warnings,[{{6,39},erl_lint,{shadowed_var,'X',generate}}]}}
],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-unused_var(doc) ->
- "Unused variable with a name that should not be introduced.";
-unused_var(suite) -> [];
+%% Unused variable with a name that should not be introduced.
unused_var(Config) when is_list(Config) ->
Ts =
[{unused_var,
@@ -244,12 +233,10 @@ unused_var(Config) when is_list(Config) ->
">>,
[warn_unused_vars],
{warnings,[{{2,33},erl_lint,{unused_var,'Y1'}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-lc(doc) ->
- "Ordinary LC expression.";
-lc(suite) -> [];
+%% Ordinary LC expression.
lc(Config) when is_list(Config) ->
Ts =
[{lc,
@@ -258,12 +245,10 @@ lc(Config) when is_list(Config) ->
">>,
[],
{warnings,[{{2,30},erl_lint,{shadowed_var,'X',generate}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-fun_clauses(doc) ->
- "Fun with several clauses.";
-fun_clauses(suite) -> [];
+%% Fun with several clauses.
fun_clauses(Config) when is_list(Config) ->
Ts =
[{fun_clauses,
@@ -279,12 +264,10 @@ fun_clauses(Config) when is_list(Config) ->
{{3,41},erl_lint,{shadowed_var,'X',generate}},
{{4,22},erl_lint,{shadowed_var,'X','fun'}},
{{4,41},erl_lint,{shadowed_var,'X',generate}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-filter_var(doc) ->
- "Variable introduced in filter.";
-filter_var(suite) -> [];
+%% Variable introduced in filter.
filter_var(Config) when is_list(Config) ->
Ts =
[{filter_var,
@@ -309,13 +292,11 @@ filter_var(Config) when is_list(Config) ->
">>,
[],
{errors,[{{2,25},erl_lint,{unsafe_var,'V',{'case',{3,19}}}}],[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-single(doc) ->
- "Unused pattern variable.";
-single(suite) -> [];
+%% Unused pattern variable.
single(Config) when is_list(Config) ->
Ts =
[{single,
@@ -325,12 +306,10 @@ single(Config) when is_list(Config) ->
">>,
[warn_unused_vars],
{warnings,[{{2,30},erl_lint,{unused_var,'Y'}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-exported_var(doc) ->
- "Exported variable in list expression (rhs of generator).";
-exported_var(suite) -> [];
+%% Exported variable in list expression (rhs of generator).
exported_var(Config) when is_list(Config) ->
Ts =
[{exported_var,
@@ -347,12 +326,10 @@ exported_var(Config) when is_list(Config) ->
[warn_export_vars],
{warnings,[{{7,37},erl_lint,{exported_var,'Z',{'case',{3,36}}}},
{{7,44},erl_lint,{exported_var,'Z',{'case',{3,36}}}}]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-generator_vars(doc) ->
- "Errors for generator variable used in list expression.";
-generator_vars(suite) -> [];
+%% Errors for generator variable used in list expression.
generator_vars(Config) when is_list(Config) ->
Ts =
[{generator_vars,
@@ -374,12 +351,10 @@ generator_vars(Config) when is_list(Config) ->
{{9,33},?QLC,{used_generator_variable,'Z'}},
{{9,40},?QLC,{used_generator_variable,'Z'}}],
[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-nomatch(doc) ->
- "Unreachable clauses also found when compiling.";
-nomatch(suite) -> [];
+%% Unreachable clauses also found when compiling.
nomatch(Config) when is_list(Config) ->
Ts =
[{unreachable1,
@@ -451,13 +426,11 @@ nomatch(Config) when is_list(Config) ->
{warnings,[{3,v3_core,nomatch}]}}
],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-errors(doc) ->
- "Errors within qlc expressions also found when compiling.";
-errors(suite) -> [];
+%% Errors within qlc expressions also found when compiling.
errors(Config) when is_list(Config) ->
Ts =
[{errors1,
@@ -466,12 +439,10 @@ errors(Config) when is_list(Config) ->
">>,
[],
{errors,[{{2,33},erl_lint,{unbound_var,'A'}}],[]}}],
- ?line [] = compile(Config, Ts),
+ [] = compile(Config, Ts),
ok.
-pattern(doc) ->
- "Patterns.";
-pattern(suite) -> [];
+%% Patterns.
pattern(Config) when is_list(Config) ->
Ts = [
<<"%% Records in patterns. No lookup.
@@ -493,14 +464,12 @@ pattern(Config) when is_list(Config) ->
end, [{<<\"hej\">>}])">>
],
- ?line run(Config, <<"-record(a, {k,v}).
+ run(Config, <<"-record(a, {k,v}).
-record(k, {t,v}).\n">>, Ts),
ok.
-eval(doc) ->
- "eval/2";
-eval(suite) -> [];
+%% eval/2
eval(Config) when is_list(Config) ->
ScratchDir = filename:join([?privdir, "scratch","."]),
@@ -616,12 +585,10 @@ eval(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-cursor(doc) ->
- "cursor/2";
-cursor(suite) -> [];
+%% cursor/2
cursor(Config) when is_list(Config) ->
ScratchDir = filename:join([?privdir, "scratch","."]),
Ts = [<<"{'EXIT',{badarg,_}} =
@@ -730,12 +697,10 @@ cursor(Config) when is_list(Config) ->
ok = qlc:delete_cursor(C2)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-fold(doc) ->
- "fold/4";
-fold(suite) -> [];
+%% fold/4
fold(Config) when is_list(Config) ->
ScratchDir = filename:join([?privdir, "scratch","."]),
Ts = [<<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
@@ -825,12 +790,10 @@ fold(Config) when is_list(Config) ->
(catch qlc:fold(F, [], Q, [{unique_all,false}]))
">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-eval_unique(doc) ->
- "Test the unique_all option of eval.";
-eval_unique(suite) -> [];
+%% Test the unique_all option of eval.
eval_unique(Config) when is_list(Config) ->
Ts = [<<"QLC1 = qlc:q([X || X <- qlc:append([[1,1,2], [1,2,3,2,3]])]),
[1,2,3] = qlc:eval(QLC1, {unique_all,true}),
@@ -922,12 +885,10 @@ eval_unique(Config) when is_list(Config) ->
{sort,{sort,{list,_},[{unique,true}]},[]} = i(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-eval_cache(doc) ->
- "Test the cache_all and unique_all options of eval.";
-eval_cache(suite) -> [];
+%% Test the cache_all and unique_all options of eval.
eval_cache(Config) when is_list(Config) ->
Ts = [
<<"E = ets:new(apa, [ordered_set]),
@@ -1056,12 +1017,10 @@ eval_cache(Config) when is_list(Config) ->
[1] = qlc:e(H, unique_all)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-append(doc) ->
- "Test the append function.";
-append(suite) -> [];
+%% Test the append function.
append(Config) when is_list(Config) ->
Ts = [<<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3], begin 10/X > 0.0 end])),
R = (catch qlc:next_answers(C)),
@@ -1121,12 +1080,12 @@ append(Config) when is_list(Config) ->
foo() -> bar">>,
%% Used to work up to R11B.
- % <<"apa = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3], ugly()])])),
- % ok.
- %
- % ugly() ->
- % [a | apa].
- % foo() -> bar">>,
+ %% <<"apa = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3], ugly()])])),
+ %% ok.
+ %%
+ %% ugly() ->
+ %% [a | apa].
+ %% foo() -> bar">>,
%% Maybe this one should fail.
@@ -1179,99 +1138,93 @@ append(Config) when is_list(Config) ->
[a,b,1,2,1,2] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-evaluator(doc) ->
- "Simple call from evaluator.";
-evaluator(suite) -> [];
+%% Simple call from evaluator.
evaluator(Config) when is_list(Config) ->
- ?line true = is_alive(),
+ true = is_alive(),
evaluator_2(Config, []),
- ?line {ok, Node} = start_node(qlc_SUITE_evaluator),
- ?line ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
- ?line ?t:stop_node(Node),
+ {ok, Node} = start_node(qlc_SUITE_evaluator),
+ ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
+ test_server:stop_node(Node),
ok.
evaluator_2(Config, Apps) ->
- ?line lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
+ lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
FileName = filename:join(?privdir, "eval"),
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([X || X <- L]),
[1,2,3] = qlc:e(H).">>),
- ?line Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
- ?line ok = file:eval(FileName, Bs),
+ Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
+ ok = file:eval(FileName, Bs),
%% The error message is "handled" a bit too much...
%% (no trace of erl_lint left)
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([X || X <- L]), qlc:e(H).">>),
- ?line {error,_} = file:eval(FileName),
+ {error,_} = file:eval(FileName),
%% Ugly error message; badarg is caught by file.erl.
- ?line ok = file:write_file(FileName,
+ ok = file:write_file(FileName,
<<"H = qlc:q([Z || {X,Y} <- [{a,2}], Z <- [Y]]), qlc:e(H).">>),
- ?line {error,_} = file:eval(FileName),
+ {error,_} = file:eval(FileName),
_ = file:delete(FileName),
ok.
start_node(Name) ->
- ?line PA = filename:dirname(code:which(?MODULE)),
- ?t:start_node(Name, slave, [{args, "-pa " ++ PA}]).
+ PA = filename:dirname(code:which(?MODULE)),
+ test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
-string_to_handle(doc) ->
- "string_to_handle/1,2.";
-string_to_handle(suite) -> [];
+%% string_to_handle/1,2.
string_to_handle(Config) when is_list(Config) ->
- ?line {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
- ?line {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
+ {'EXIT',{badarg,_}} =
(catch qlc:string_to_handle("[X || X <- [a].", unique_all)),
- ?line R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
- ?line "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
- ?line {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
- ?line {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
- ?line R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
+ R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
+ "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
+ {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
+ {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
+ R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
qlc:string_to_handle("bad."),
- ?line "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
- ?line R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
+ "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
+ R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
qlc:string_to_handle("[X || begin Y = [1,2], true end, X <- Y]."),
- ?line "1: generated variable 'Y'" ++ _ =
+ "1: generated variable 'Y'" ++ _ =
lists:flatten(qlc:format_error(R4)),
- ?line {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
- ?line H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
- ?line [1,2] = qlc:e(H1),
- ?line H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
+ {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
+ H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
+ [1,2] = qlc:e(H1),
+ H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
"qlc:e(qlc:q([X || X <- [c,d,e]])))]."),
- ?line [a,b,c,d,e] = qlc:e(H2),
+ [a,b,c,d,e] = qlc:e(H2),
%% The generated fun has many arguments (erl_eval has a maximum of 20).
- ?line H3 = qlc:string_to_handle(
+ H3 = qlc:string_to_handle(
"[{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||"
" {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <- []]."),
- ?line [] = qlc:e(H3),
- ?line Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
- ?line H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
- ?line [1,2,3] = qlc:e(H4),
- ?line H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
- ?line [1,2] = qlc:e(H5),
-
- ?line Ets = ets:new(test, []),
- ?line true = ets:insert(Ets, [{1}]),
- ?line Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
- ?line Q = "[X || {X} <- ets:table(E)].",
- ?line [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
- ?line [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
- ?line [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
- ?line {'EXIT',{badarg,_}} =
+ [] = qlc:e(H3),
+ Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
+ H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
+ [1,2,3] = qlc:e(H4),
+ H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
+ [1,2] = qlc:e(H5),
+
+ Ets = ets:new(test, []),
+ true = ets:insert(Ets, [{1}]),
+ Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
+ Q = "[X || {X} <- ets:table(E)].",
+ [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
+ [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
+ [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
+ {'EXIT',{badarg,_}} =
(catch qlc:string_to_handle(Q, {max_lookup,-1}, Bs2)),
- ?line {'EXIT', {no_lookup_to_carry_out, _}} =
+ {'EXIT', {no_lookup_to_carry_out, _}} =
(catch qlc:e(qlc:string_to_handle(Q, {lookup,true}, Bs2))),
- ?line ets:delete(Ets),
+ ets:delete(Ets),
ok.
-table(doc) ->
- "table";
-table(suite) -> [];
+%% table
table(Config) when is_list(Config) ->
dets:start(),
Ts = [
@@ -1353,11 +1306,11 @@ table(Config) when is_list(Config) ->
ets:delete(E)">>,
%% The info tag num_of_objects is currently not used.
-% <<"E = ets:new(test, [ordered_set]),
-% true = ets:insert(E, [{1,a},{2,b},{3,c}]),
-% H = qlc:q([X || X <- qlc_SUITE:bad_table_info_fun_n_objects(E)]),
-% {'EXIT', finito} = (catch {any_term,qlc:e(H)}),
-% ets:delete(E)">>,
+%% <<"E = ets:new(test, [ordered_set]),
+%% true = ets:insert(E, [{1,a},{2,b},{3,c}]),
+%% H = qlc:q([X || X <- qlc_SUITE:bad_table_info_fun_n_objects(E)]),
+%% {'EXIT', finito} = (catch {any_term,qlc:e(H)}),
+%% ets:delete(E)">>,
<<"E = ets:new(test, [ordered_set]),
true = ets:insert(E, [{1,a},{2,b},{3,c}]),
@@ -1473,7 +1426,7 @@ table(Config) when is_list(Config) ->
[1,2] = lookup_keys(Q)
end, [{1,1},{2,2}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
Ts2 = [
%% [T || P <- Table, F] turned into a match spec. Records needed.
@@ -1484,13 +1437,11 @@ table(Config) when is_list(Config) ->
[{a,1,2},{a,3,4}] = lists:sort(qlc:eval(QH)),
ets:delete(E)">>
],
- ?line run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
+ run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
ok.
-process_dies(doc) ->
- "Caller or cursor process dies.";
-process_dies(suite) -> [];
+%% Caller or cursor process dies.
process_dies(Config) when is_list(Config) ->
Ts = [
<<"E = ets:new(test, []),
@@ -1629,12 +1580,10 @@ process_dies(Config) when is_list(Config) ->
true = ets:delete(E), ok">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-sort(doc) ->
- "The sort option.";
-sort(suite) -> [];
+%% The sort option.
sort(Config) when is_list(Config) ->
Ts = [
<<"H = qlc:q([X || X <- qlc:sort([1,2,3,2], {unique,true})]),
@@ -1741,12 +1690,10 @@ sort(Config) when is_list(Config) ->
end
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-keysort(doc) ->
- "The sort option.";
-keysort(suite) -> [];
+%% The sort option.
keysort(Config) when is_list(Config) ->
Ts = [
@@ -1865,13 +1812,11 @@ keysort(Config) when is_list(Config) ->
100003 = length(R)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-filesort(doc) ->
- "keysort/1,2, using a file.";
-filesort(suite) -> [];
+%% keysort/1,2, using a file.
filesort(Config) when is_list(Config) ->
Ts = [
<<"Q = qlc:q([X || X <- [{3},{1},{2}]]),
@@ -1879,13 +1824,11 @@ filesort(Config) when is_list(Config) ->
Q2 = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:keysort([1],Q,Opts)]),
[{{1},1},{{2},1},{{3},1},{{1},2},{{2},2},{{3},2}] = qlc:e(Q2)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-cache(doc) ->
- "The cache option.";
-cache(suite) -> [];
+%% The cache option.
cache(Config) when is_list(Config) ->
Ts = [
<<"{'EXIT', {badarg, _}} = (catch qlc:q([X || X <- [1,2]], badarg))">>,
@@ -2043,12 +1986,10 @@ cache(Config) when is_list(Config) ->
[]} = i(H, cache_all)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-cache_list(doc) ->
- "OTP-6038. The {cache,list} option.";
-cache_list(suite) -> [];
+%% OTP-6038. The {cache,list} option.
cache_list(Config) when is_list(Config) ->
Ts = [
begin
@@ -2334,12 +2275,10 @@ cache_list(Config) when is_list(Config) ->
{'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, foo}))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-filter(doc) ->
- "Filters and match specs.";
-filter(suite) -> [];
+%% Filters and match specs.
filter(Config) when is_list(Config) ->
Ts = [
<<"L = [1,2,3,4,5],
@@ -2461,12 +2400,10 @@ filter(Config) when is_list(Config) ->
[{2,b},{2,c},{3,b},{3,c}] = qlc:e(H)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-info(doc) ->
- "info/2.";
-info(suite) -> [];
+%% info/2.
info(Config) when is_list(Config) ->
Ts = [
<<"{list, [1,2]} = i(qlc:q([X || X <- [1,2]])),
@@ -2686,12 +2623,10 @@ info(Config) when is_list(Config) ->
[{4},{5},{6}] = qlc:e(F(3))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-nested_info(doc) ->
- "Nested QLC expressions. QLC expressions in filter and template.";
-nested_info(suite) -> [];
+%% Nested QLC expressions. QLC expressions in filter and template.
nested_info(Config) when is_list(Config) ->
Ts = [
<<"L = [{1,a},{2,b},{3,c}],
@@ -2792,13 +2727,11 @@ nested_info(Config) when is_list(Config) ->
[{1,1},{1,1},{1,2},{1,2},{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-lookup1(doc) ->
- "Lookup keys. Mostly test of patterns.";
-lookup1(suite) -> [];
+%% Lookup keys. Mostly test of patterns.
lookup1(Config) when is_list(Config) ->
Ts = [
<<"etsc(fun(E) ->
@@ -3003,12 +2936,10 @@ lookup1(Config) when is_list(Config) ->
[]}
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-lookup2(doc) ->
- "Lookup keys. Mostly test of filters.";
-lookup2(suite) -> [];
+%% Lookup keys. Mostly test of filters.
lookup2(Config) when is_list(Config) ->
Ts = [
<<"%% Only guards are inspected. No lookup.
@@ -3708,9 +3639,7 @@ lookup2(Config) when is_list(Config) ->
ok.
-lookup_rec(doc) ->
- "Lookup keys. With records.";
-lookup_rec(suite) -> [];
+%% Lookup keys. With records.
lookup_rec(Config) when is_list(Config) ->
Ts = [
<<"etsc(fun(E) ->
@@ -3778,12 +3707,10 @@ lookup_rec(Config) when is_list(Config) ->
[_] = lookup_keys(Q)
end, [{keypos,2}], [#r{a=foo}])">>
],
- ?line run(Config, <<"-record(r, {a}).\n">>, Ts),
+ run(Config, <<"-record(r, {a}).\n">>, Ts),
ok.
-indices(doc) ->
- "Using indices for lookup.";
-indices(suite) -> [];
+%% Using indices for lookup.
indices(Config) when is_list(Config) ->
Ts = [
<<"L = [{1,a},{2,b},{3,c}],
@@ -3845,12 +3772,10 @@ indices(Config) when is_list(Config) ->
[{c,3,z,w}] = qlc:eval(QH)">>
],
- ?line run(Config, <<"-record(r, {a}).\n">>, Ts),
+ run(Config, <<"-record(r, {a}).\n">>, Ts),
ok.
-pre_fun(doc) ->
- "Test the table/2 callback functions parent_fun and stop_fun.";
-pre_fun(suite) -> [];
+%% Test the table/2 callback functions parent_fun and stop_fun.
pre_fun(Config) when is_list(Config) ->
Ts = [
<<"PF = process_flag(trap_exit, true),
@@ -3926,12 +3851,10 @@ pre_fun(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-skip_filters(doc) ->
- "Lookup keys. With records.";
-skip_filters(suite) -> [];
+%% Lookup keys. With records.
skip_filters(Config) when is_list(Config) ->
%% Skipped filters
TsS = [
@@ -4051,7 +3974,7 @@ skip_filters(Config) when is_list(Config) ->
end, [{0},{1},{2},{3},{4}])">>
],
- ?line run(Config, TsS),
+ run(Config, TsS),
Ts = [
<<"etsc(fun(E) ->
@@ -4329,14 +4252,12 @@ skip_filters(Config) when is_list(Config) ->
end, [{1},{2},{3}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-ets(doc) ->
- "ets:table/1,2.";
-ets(suite) -> [];
+%% ets:table/1,2.
ets(Config) when is_list(Config) ->
Ts = [
<<"E = ets:new(t, [ordered_set]),
@@ -4377,12 +4298,10 @@ ets(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-dets(doc) ->
- "dets:table/1,2.";
-dets(suite) -> [];
+%% dets:table/1,2.
dets(Config) when is_list(Config) ->
dets:start(),
T = t,
@@ -4475,14 +4394,12 @@ dets(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
_ = file:delete(Fname),
ok.
-join_option(doc) ->
- "The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.";
-join_option(suite) -> [];
+%% The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.
join_option(Config) when is_list(Config) ->
Ts = [
<<"Q1 = qlc:q([X || X <- [1,2,3]],{join,merge}),
@@ -4607,7 +4524,7 @@ join_option(Config) when is_list(Config) ->
ets:delete(E1)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% The 'cache' and 'unique' options of qlc/2 affects join.
CUTs = [
@@ -4655,13 +4572,11 @@ join_option(Config) when is_list(Config) ->
_],[{unique,true}]} = i(Q, Options),
[{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q, Options)">>
],
- ?line run(Config, CUTs),
+ run(Config, CUTs),
ok.
-join_filter(doc) ->
- "Various aspects of filters and join.";
-join_filter(suite) -> [];
+%% Various aspects of filters and join.
join_filter(Config) when is_list(Config) ->
Ts = [
<<"E1 = create_ets(1, 10),
@@ -4698,12 +4613,10 @@ join_filter(Config) when is_list(Config) ->
end, [{a},{b},{c}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-join_lookup(doc) ->
- "Lookup join.";
-join_lookup(suite) -> [];
+%% Lookup join.
join_lookup(Config) when is_list(Config) ->
Ts = [
<<"E1 = create_ets(1, 10),
@@ -4793,12 +4706,10 @@ join_lookup(Config) when is_list(Config) ->
ets:delete(E)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-join_merge(doc) ->
- "Merge join.";
-join_merge(suite) -> [];
+%% Merge join.
join_merge(Config) when is_list(Config) ->
Ts = [
<<"Q = qlc:q([{X,Y} || {X} <- [], {Y} <- [{1}], X =:= Y],
@@ -5070,7 +4981,7 @@ join_merge(Config) when is_list(Config) ->
[{2,a}] = qlc:e(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% Small examples. Returning an error term.
ETs = [
@@ -5249,7 +5160,7 @@ join_merge(Config) when is_list(Config) ->
err = qlc:e(Q)">>
],
- ?line run(Config, ETs),
+ run(Config, ETs),
%% Mostly examples where temporary files are needed while merging.
FTs = [
@@ -5408,13 +5319,11 @@ join_merge(Config) when is_list(Config) ->
],
- ?line run(Config, FTs),
+ run(Config, FTs),
ok.
-join_sort(doc) ->
- "Merge join optimizations (avoid unnecessary sorting).";
-join_sort(suite) -> [];
+%% Merge join optimizations (avoid unnecessary sorting).
join_sort(Config) when is_list(Config) ->
Ts = [
<<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
@@ -5694,12 +5603,10 @@ join_sort(Config) when is_list(Config) ->
end, [{1,2},{3,4}])">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-join_complex(doc) ->
- "Join of more than two columns.";
-join_complex(suite) -> [];
+%% Join of more than two columns.
join_complex(Config) when is_list(Config) ->
Ts = [{three,
<<"three() ->
@@ -5727,7 +5634,7 @@ join_complex(Config) when is_list(Config) ->
{warnings,[{2,qlc,too_many_joins}]}}
],
- ?line compile(Config, Ts),
+ compile(Config, Ts),
Ts2 = [{three,
<<"three() ->
@@ -5756,14 +5663,12 @@ join_complex(Config) when is_list(Config) ->
{[],["cannot handle more than one join efficiently"]}}
],
- ?line compile_format(Config, Ts2),
+ compile_format(Config, Ts2),
ok.
-otp_5644(doc) ->
- "OTP-5644. Handle the new language element M:F/A.";
-otp_5644(suite) -> [];
+%% OTP-5644. Handle the new language element M:F/A.
otp_5644(Config) when is_list(Config) ->
Ts = [
<<"Q = qlc:q([fun modul:mfa/0 || _ <- [1,2],
@@ -5771,12 +5676,10 @@ otp_5644(Config) when is_list(Config) ->
[_,_] = qlc:eval(Q)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-otp_5195(doc) ->
- "OTP-5195. Allow traverse functions returning terms.";
-otp_5195(suite) -> [];
+%% OTP-5195. Allow traverse functions returning terms.
otp_5195(Config) when is_list(Config) ->
%% Several minor improvements have been implemented in OTP-5195.
%% The test cases are spread all over... except these.
@@ -5854,7 +5757,7 @@ otp_5195(Config) when is_list(Config) ->
],
- ?line run(Config, Ts),
+ run(Config, Ts),
Ts2 = [<<"Q = qlc:q([{X,Y} || {X} <- [{1},{2},{3}],
begin
@@ -5863,13 +5766,11 @@ otp_5195(Config) when is_list(Config) ->
end,
X =:= Y]),
[{3,3}] = qlc:e(Q)">>],
- ?line run(Config, Ts2),
+ run(Config, Ts2),
ok.
-otp_6038_bug(doc) ->
- "OTP-6038. Bug fixes: unique and keysort; cache.";
-otp_6038_bug(suite) -> [];
+%% OTP-6038. Bug fixes: unique and keysort; cache.
otp_6038_bug(Config) when is_list(Config) ->
%% The 'unique' option can no longer be merged with the keysort options.
%% This used to return [{1,a},{1,c},{2,b},{2,d}], but since
@@ -5879,7 +5780,7 @@ otp_6038_bug(Config) when is_list(Config) ->
H2 = qlc:keysort(1, H1, [{unique,true}]),
[{1,a},{2,b}] = qlc:e(H2)">>],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% Sometimes the cache options did not empty the correct tables.
CTs = [
@@ -5908,13 +5809,11 @@ otp_6038_bug(Config) when is_list(Config) ->
L = [{X,Y} || X <- [1,2], Y <- L4],
true = R =:= L">>
],
- ?line run(Config, CTs),
+ run(Config, CTs),
ok.
-otp_6359(doc) ->
- "OTP-6359. dets:select() never returns the empty list.";
-otp_6359(suite) -> [];
+%% OTP-6359. dets:select() never returns the empty list.
otp_6359(Config) when is_list(Config) ->
dets:start(),
T = luna,
@@ -5933,12 +5832,10 @@ otp_6359(Config) when is_list(Config) ->
ok">>]
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
-otp_6562(doc) ->
- "OTP-6562. compressed = false (should be []) when sorting before join.";
-otp_6562(suite) -> [];
+%% OTP-6562. compressed = false (should be []) when sorting before join.
otp_6562(Config) when is_list(Config) ->
Bug = [
%% This example uses a file to sort E2 on the second column. It is
@@ -5957,7 +5854,7 @@ otp_6562(Config) when is_list(Config) ->
ets:delete(E1),
ets:delete(E2)">>
],
- ?line run(Config, Bug),
+ run(Config, Bug),
Bits = [
{otp_6562_1,
@@ -5969,18 +5866,16 @@ otp_6562(Config) when is_list(Config) ->
{errors,[{2,qlc,binary_generator}],
[]}}
],
- ?line [] = compile(Config, Bits),
+ [] = compile(Config, Bits),
- ?line R1 = {error,qlc,{1,qlc,binary_generator}}
+ R1 = {error,qlc,{1,qlc,binary_generator}}
= qlc:string_to_handle("[X || <<X:8>> <= <<\"hej\">>]."),
- ?line "1: cannot handle binary generators\n" =
+ "1: cannot handle binary generators\n" =
lists:flatten(qlc:format_error(R1)),
ok.
-otp_6590(doc) ->
- "OTP-6590. Bug fix (join info).";
-otp_6590(suite) -> [];
+%% OTP-6590. Bug fix (join info).
otp_6590(Config) when is_list(Config) ->
Ts = [<<"fun(Tab1Value) ->
Q = qlc:q([T1#tab1.id || T1 <- [#tab1{id = id1,
@@ -5992,13 +5887,11 @@ otp_6590(Config) when is_list(Config) ->
[id1] = qlc:e(Q)
end(v)">>],
- ?line run(Config, <<"-record(tab1, {id, tab2_id, value}).
+ run(Config, <<"-record(tab1, {id, tab2_id, value}).
-record(tab2, {id, value}).\n">>, Ts),
ok.
-otp_6673(doc) ->
- "OTP-6673. Optimizations and fixes.";
-otp_6673(suite) -> [];
+%% OTP-6673. Optimizations and fixes.
otp_6673(Config) when is_list(Config) ->
Ts_PT =
[<<"etsc(fun(E1) ->
@@ -6054,7 +5947,7 @@ otp_6673(Config) when is_list(Config) ->
end,
[{1,x},{2,y},{3,z}])">>],
- ?line run(Config, Ts_PT),
+ run(Config, Ts_PT),
MS = ets:fun2ms(fun({X,_Y}=T) when X > 1 -> T end),
Ts_RT = [
@@ -6091,13 +5984,11 @@ otp_6673(Config) when is_list(Config) ->
end, [{x,1},{y,2},{z,3}])">>
],
- ?line run(Config, Ts_RT),
+ run(Config, Ts_RT),
ok.
-otp_6964(doc) ->
- "OTP-6964. New option 'tmpdir_usage'.";
-otp_6964(suite) -> [];
+%% OTP-6964. New option 'tmpdir_usage'.
otp_6964(Config) when is_list(Config) ->
T1 = [
<<"Q1 = qlc:q([{X} || X <- [1,2]]),
@@ -6131,7 +6022,7 @@ otp_6964(Config) when is_list(Config) ->
_ = erlang:system_flag(backtrace_depth, D)
end,
qlc_SUITE:uninstall_error_logger()">>],
- ?line run(Config, T1),
+ run(Config, T1),
T2 = [
<<"%% File sorter.
@@ -6164,7 +6055,7 @@ otp_6964(Config) when is_list(Config) ->
{info, caching} = qlc_SUITE:read_error_logger(),
qlc_SUITE:uninstall_error_logger()">>],
- ?line run(Config, T2),
+ run(Config, T2),
T3 = [
<<"%% sort/keysort
@@ -6194,7 +6085,7 @@ otp_6964(Config) when is_list(Config) ->
qlc_SUITE:uninstall_error_logger(),
ets:delete(E1),
ets:delete(E2)">>],
- ?line run(Config, T3),
+ run(Config, T3),
T4 = [
<<"%% cache list
@@ -6225,18 +6116,16 @@ otp_6964(Config) when is_list(Config) ->
lists:flatten(qlc:format_error(ErrReply))
end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
I <- lists:seq(1, 10)])">>],
- ?line run(Config, T4),
+ run(Config, T4),
ok.
-otp_7238(doc) ->
- "OTP-7238. info-option 'depth', &c.";
-otp_7238(suite) -> [];
+%% OTP-7238. info-option 'depth', &c.
otp_7238(Config) when is_list(Config) ->
dets:start(),
T = otp_7238,
Fname = filename(T, Config),
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
%% A few more warnings.
T1 = [
@@ -6365,7 +6254,7 @@ otp_7238(Config) when is_list(Config) ->
[],
{warnings,[{2,sys_core_fold,no_clause_match}]}}
],
- ?line [] = compile(Config, T1),
+ [] = compile(Config, T1),
%% 'depth' is a new option used by info()
T2 = [
@@ -6591,7 +6480,7 @@ otp_7238(Config) when is_list(Config) ->
qlc:info(Q, [{format,abstract_code},{depth, 2}])">>
],
- ?line run(Config, T2),
+ run(Config, T2),
T3 = [
%% {nomatch_6,
@@ -6607,7 +6496,7 @@ otp_7238(Config) when is_list(Config) ->
%% [],
%% {[],["pattern cannot possibly match"]}}
],
- ?line compile_format(Config, T3),
+ compile_format(Config, T3),
%% *Very* simple test - just check that it doesn't crash.
Type = [{cres,
@@ -6615,13 +6504,11 @@ otp_7238(Config) when is_list(Config) ->
{'EXIT',{{badfun,_},_}} = (catch qlc:e(Q))">>,
[type_checker],
[]}],
- ?line run(Config, Type),
+ run(Config, Type),
ok.
-otp_7114(doc) ->
- "OTP-7114. Match spec, table and duplicated objects..";
-otp_7114(suite) -> [];
+%% OTP-7114. Match spec, table and duplicated objects...
otp_7114(Config) when is_list(Config) ->
Ts = [<<"T = ets:new(t, [bag]),
[ets:insert(T, {t, I, I div 2}) || I <- lists:seq(1,10)],
@@ -6632,11 +6519,9 @@ otp_7114(Config) when is_list(Config) ->
[0,1,2,3,4,5] = qlc:e(qlc:sort(qlc:e(Q1)), unique_all),
ets:delete(T),
ok">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
-otp_7232(doc) ->
- "OTP-7232. qlc:info() bug (pids, ports, refs, funs).";
-otp_7232(suite) -> [];
+%% OTP-7232. qlc:info() bug (pids, ports, refs, funs).
otp_7232(Config) when is_list(Config) ->
Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
erlang:make_ref()],
@@ -6664,11 +6549,9 @@ otp_7232(Config) when is_list(Config) ->
\"[<<8,1:1>>]\" = qlc:info(Q)">>
],
- ?line run(Config, Ts).
+ run(Config, Ts).
-otp_7552(doc) ->
- "OTP-7552. Merge join bug.";
-otp_7552(suite) -> [];
+%% OTP-7552. Merge join bug.
otp_7552(Config) when is_list(Config) ->
%% The poor performance cannot be observed unless the
%% (redundant) join filter is skipped.
@@ -6691,11 +6574,9 @@ otp_7552(Config) when is_list(Config) ->
Qn = F(nested_loop),
true = lists:sort(qlc:e(Qm, {max_list_size,20})) =:=
lists:sort(qlc:e(Qn))">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
-otp_7714(doc) ->
- "OTP-7714. Merge join bug.";
-otp_7714(suite) -> [];
+%% OTP-7714. Merge join bug.
otp_7714(Config) when is_list(Config) ->
%% The original example uses Mnesia. This one does not.
Ts = [<<"E1 = ets:new(set,[]),
@@ -6710,11 +6591,9 @@ otp_7714(Config) when is_list(Config) ->
[{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)),
ets:delete(E1),
ets:delete(E2)">>],
- ?line run(Config, Ts).
+ run(Config, Ts).
-otp_11758(doc) ->
- "OTP-11758. Bug.";
-otp_11758(suite) -> [];
+%% OTP-11758. Bug.
otp_11758(Config) when is_list(Config) ->
Ts = [<<"T = ets:new(r, [{keypos, 2}]),
L = [{rrr, xxx, aaa}, {rrr, yyy, bbb}],
@@ -6725,12 +6604,10 @@ otp_11758(Config) when is_list(Config) ->
ets:delete(T)">>],
run(Config, Ts).
-otp_6674(doc) ->
- "OTP-6674. match/comparison.";
-otp_6674(suite) -> [];
+%% OTP-6674. match/comparison.
otp_6674(Config) when is_list(Config) ->
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
Ts = [%% lookup join
<<"E = ets:new(join, [ordered_set]),
@@ -7153,11 +7030,9 @@ otp_6674(Config) when is_list(Config) ->
],
- ?line run(Config, Ts).
+ run(Config, Ts).
-otp_12946(doc) ->
- ["Syntax error."];
-otp_12946(suite) -> [];
+%% Syntax error.
otp_12946(Config) when is_list(Config) ->
Text =
<<"-export([init/0]).
@@ -7167,12 +7042,10 @@ otp_12946(Config) when is_list(Config) ->
{errors,[{4,erl_parse,_}],[]} = compile_file(Config, Text, []),
ok.
-manpage(doc) ->
- "Examples from qlc(3).";
-manpage(suite) -> [];
+%% Examples from qlc(3).
manpage(Config) when is_list(Config) ->
- ?line ok = compile_gb_table(Config),
+ ok = compile_gb_table(Config),
Ts = [
<<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
@@ -7327,7 +7200,7 @@ manpage(Config) when is_list(Config) ->
ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))\",
L = qlc:info(QH)">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
L = [1,2,3],
Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
@@ -7345,7 +7218,7 @@ manpage(Config) when is_list(Config) ->
true = qlc:info(QH1) =:= qlc:info(QH2),
true = ets:delete(Tab)">>]],
- ?line run(Config, ETs),
+ run(Config, ETs),
%% dets(3)
DTs = [
@@ -7358,16 +7231,16 @@ manpage(Config) when is_list(Config) ->
true = qlc:info(QH1) =:= qlc:info(QH2),
ok = dets:close(T)">>]],
- ?line run(Config, DTs),
+ run(Config, DTs),
ok.
compile_gb_table(Config) ->
GB_table_file = filename("gb_table.erl", Config),
- ?line ok = file:write_file(GB_table_file, gb_table()),
- ?line {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
- ?line code:purge(gb_table),
- ?line {module, gb_table} =
+ ok = file:write_file(GB_table_file, gb_table()),
+ {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
+ code:purge(gb_table),
+ {module, gb_table} =
code:load_abs(filename:rootname(GB_table_file)),
ok.
@@ -7433,9 +7306,7 @@ gb_iter(I0, N, EFun) ->
">>.
-backward(doc) ->
- "OTP-6674. Join info and extra constants.";
-backward(suite) -> [];
+%% OTP-6674. Join info and extra constants.
backward(Config) when is_list(Config) ->
try_old_join_info(Config),
ok.
@@ -7470,9 +7341,6 @@ try_old_join_info(Config) ->
qlc:info(H2, {format,debug}),
[{1,1},{2,2}] = qlc:e(H2).
-forward(doc) ->
- "";
-forward(suite) -> [];
forward(Config) when is_list(Config) ->
Ts = [
%% LC_fun() returns something unknown.
@@ -7481,12 +7349,12 @@ forward(Config) when is_list(Config) ->
{'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
%% 'f1' should be used for new stuff that does not interfer with old behavior
-% %% The unused element 'f1' of #qlc_table seems to be used.
-% <<"DF = fun() -> foo end,
-% FakeH = {qlc_handle,{qlc_table,DF,
-% true,DF,DF,DF,DF,DF,
-% undefined,not_undefined,undefined,no_match_spec}},
-% {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
+%% %% The unused element 'f1' of #qlc_table seems to be used.
+%% <<"DF = fun() -> foo end,
+%% FakeH = {qlc_handle,{qlc_table,DF,
+%% true,DF,DF,DF,DF,DF,
+%% undefined,not_undefined,undefined,no_match_spec}},
+%% {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
%% #qlc_opt has changed.
<<"H = qlc:q([X || X <- []]),
@@ -7495,7 +7363,7 @@ forward(Config) when is_list(Config) ->
{'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>
],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
eep37(Config) when is_list(Config) ->
@@ -7955,7 +7823,7 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
R = case catch Mod:function() of
{'EXIT', _Reason} = Error ->
- ?t:format("failed, got ~p~n", [Error]),
+ io:format("failed, got ~p~n", [Error]),
fail(SourceFile);
Reply ->
Reply
@@ -7966,7 +7834,7 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
{file, cover_compiled} ->
ok;
{file, _} ->
- ?t:format("qlc_pt was loaded in runtime~n", []),
+ io:format("qlc_pt was loaded in runtime~n", []),
fail(SourceFile);
false ->
ok
@@ -8167,16 +8035,15 @@ warnings(File, Ws) ->
end.
expected(Test, Expected, Got, File) ->
- ?t:format("~nTest ~p failed. ", [Test]),
+ io:format("~nTest ~p failed. ", [Test]),
expected(Expected, Got, File).
expected(Expected, Got, File) ->
- ?t:format("Expected~n ~p~n, but got~n ~p~n", [Expected, Got]),
+ io:format("Expected~n ~p~n, but got~n ~p~n", [Expected, Got]),
fail(File).
fail(Source) ->
- io:format("failed~n"),
- ?t:fail({failed,testcase,on,Source}).
+ ct:fail({failed,testcase,on,Source}).
%% Copied from global_SUITE.erl.
@@ -8197,8 +8064,8 @@ read_error_logger() ->
{error, Pid, Tuple} ->
{error, Pid, Tuple}
after 1000 ->
- ?line io:format("No reply after 1 s\n", []),
- ?line ?t:fail()
+ io:format("No reply after 1 s\n", []),
+ ct:fail(failed)
end.
%%-----------------------------------------------------------------