~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/test/qlc_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%%%----------------------------------------------------------------
20
20
%%% Purpose:Test Suite for the 'qlc' module.
21
21
%%%-----------------------------------------------------------------
22
22
-module(qlc_SUITE).
 
23
-compile(r12).
23
24
 
24
25
-define(QLC, qlc).
25
26
-define(QLCs, "qlc").
42
43
-define(testcase, current_testcase). % don't know
43
44
-define(t, test_server).
44
45
-else.
45
 
-include("test_server.hrl").
 
46
-include_lib("test_server/include/test_server.hrl").
46
47
-define(datadir, ?config(data_dir, Config)).
47
48
-define(privdir, ?config(priv_dir, Config)).
48
49
-define(testcase, ?config(?TESTCASE, Config)).
50
51
 
51
52
-include_lib("stdlib/include/ms_transform.hrl").
52
53
 
53
 
-export([all/1, init_per_testcase/2, fin_per_testcase/2]).
54
 
 
55
 
-export([parse_transform/1, 
56
 
             badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
57
 
             filter_var/1, single/1, exported_var/1, generator_vars/1,
58
 
             nomatch/1, errors/1, pattern/1, 
59
 
 
60
 
         evaluation/1, 
61
 
             eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1, 
62
 
             evaluator/1, string_to_handle/1, table/1, process_dies/1, 
63
 
             sort/1, keysort/1, filesort/1, cache/1, cache_list/1, filter/1, 
64
 
             info/1, nested_info/1, lookup1/1, lookup2/1, lookup_rec/1, 
65
 
             indices/1, pre_fun/1, skip_filters/1,
66
 
 
67
 
         table_impls/1,
68
 
             ets/1, dets/1,
69
 
 
70
 
         join/1,
71
 
             join_option/1, join_filter/1, join_lookup/1, join_merge/1,
72
 
             join_sort/1, join_complex/1,
73
 
 
74
 
         tickets/1,
75
 
             otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1,
76
 
             otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1,
77
 
             otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1,
78
 
 
79
 
         manpage/1,
80
 
 
81
 
         compat/1,
82
 
             backward/1, forward/1]).
 
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, 
 
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,
 
77
 
 
78
          manpage/1,
 
79
 
 
80
          backward/1, forward/1]).
83
81
 
84
82
%% Internal exports.
85
83
-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
113
111
    ?line Dog = ?t:timetrap(?default_timeout),
114
112
    [{?TESTCASE, Case}, {watchdog, Dog} | Config].
115
113
 
116
 
fin_per_testcase(_Case, _Config) ->
 
114
end_per_testcase(_Case, _Config) ->
117
115
    Dog = ?config(watchdog, _Config),
118
116
    test_server:timetrap_cancel(Dog),
119
117
    ok.
120
118
 
121
 
all(suite) -> 
122
 
    [parse_transform, evaluation, table_impls, join, tickets, manpage, compat].
123
 
 
124
 
parse_transform(suite) ->
125
 
    [badarg, nested_qlc, unused_var, lc, fun_clauses, filter_var,
126
 
     single, exported_var, generator_vars, nomatch, errors, pattern].
 
119
suite() -> [{ct_hooks,[ts_install_cth]}].
 
120
 
 
121
all() -> 
 
122
    [{group, parse_transform}, {group, evaluation},
 
123
     {group, table_impls}, {group, join}, {group, tickets},
 
124
     manpage, {group, compat}].
 
125
 
 
126
groups() -> 
 
127
    [{parse_transform, [],
 
128
      [badarg, nested_qlc, unused_var, lc, fun_clauses,
 
129
       filter_var, single, exported_var, generator_vars,
 
130
       nomatch, errors, pattern]},
 
131
     {evaluation, [],
 
132
      [eval, cursor, fold, eval_unique, eval_cache, append,
 
133
       evaluator, string_to_handle, table, process_dies, sort,
 
134
       keysort, filesort, cache, cache_list, filter, info,
 
135
       nested_info, lookup1, lookup2, lookup_rec, indices,
 
136
       pre_fun, skip_filters]},
 
137
     {table_impls, [], [ets, dets]},
 
138
     {join, [],
 
139
      [join_option, join_filter, join_lookup, join_merge,
 
140
       join_sort, join_complex]},
 
141
     {tickets, [],
 
142
      [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562,
 
143
       otp_6590, otp_6673, otp_6964, otp_7114, otp_7232,
 
144
       otp_7238, otp_7552, otp_6674, otp_7714]},
 
145
     {compat, [], [backward, forward]}].
 
146
 
 
147
init_per_suite(Config) ->
 
148
    Config.
 
149
 
 
150
end_per_suite(_Config) ->
 
151
    ok.
 
152
 
 
153
init_per_group(_GroupName, Config) ->
 
154
    Config.
 
155
 
 
156
end_per_group(_GroupName, Config) ->
 
157
    Config.
127
158
 
128
159
badarg(doc) ->
129
160
    "Badarg.";
460
491
                         -record(k, {t,v}).\n">>, Ts),
461
492
    ok.
462
493
 
463
 
evaluation(suite) ->
464
 
    [eval, cursor, fold, eval_unique, eval_cache, append, evaluator, 
465
 
     string_to_handle, table, process_dies, sort, keysort, filesort, cache,
466
 
     cache_list, filter, info, nested_info, lookup1, lookup2, lookup_rec, 
467
 
     indices, pre_fun, skip_filters].
468
494
 
469
495
eval(doc) ->
470
496
    "eval/2";
3183
3209
                 [] = qlc:e(Q),
3184
3210
                 false = lookup_keys(Q)
3185
3211
         end, [{1,b},{2,3}])">>,
3186
 
        {warnings,[{{3,48},qlc,nomatch_filter}]}},
 
3212
        {warnings,[{2,sys_core_fold,nomatch_guard},
 
3213
                   {3,qlc,nomatch_filter},
 
3214
                   {3,sys_core_fold,{eval_failure,badarg}}]}},
3187
3215
 
3188
3216
       <<"etsc(fun(E) ->
3189
3217
                Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
4294
4322
 
4295
4323
    ok.
4296
4324
 
4297
 
table_impls(suite) ->
4298
 
    [ets, dets].
4299
4325
 
4300
4326
ets(doc) ->
4301
4327
    "ets:table/1,2.";
4442
4468
    _ = file:delete(Fname),
4443
4469
    ok.
4444
4470
 
4445
 
join(suite) ->
4446
 
    [join_option, join_filter, join_lookup, join_merge, 
4447
 
     join_sort, join_complex].
4448
4471
 
4449
4472
join_option(doc) ->
4450
4473
    "The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.";
5726
5749
 
5727
5750
    ok.
5728
5751
 
5729
 
tickets(suite) ->
5730
 
    [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562, otp_6590, 
5731
 
     otp_6673, otp_6964, otp_7114, otp_7232, otp_7238, otp_7552, otp_6674,
5732
 
     otp_7714].
5733
5752
 
5734
5753
otp_5644(doc) ->
5735
5754
    "OTP-5644. Handle the new language element M:F/A.";
7375
7394
    end.
7376
7395
    ">>.
7377
7396
 
7378
 
compat(suite) ->
7379
 
    [backward, forward].
7380
7397
 
7381
7398
backward(doc) ->
7382
7399
    "OTP-6674. Join info and extra constants.";