~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. 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
-module(ms_transform_SUITE).
56
56
    [];
57
57
andalso_orelse(doc) ->
58
58
    ["Tests that andalso and orelse are allowed in guards."];
59
 
andalso_orelse(Config) when list(Config) ->
 
59
andalso_orelse(Config) when is_list(Config) ->
60
60
    ?line setup(Config),
61
61
    ?line [{{'$1','$2'},
62
62
            [{'and',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
93
93
    [];
94
94
bitsyntax(doc) ->
95
95
    ["Tests that bitsyntax works and does not work where appropriate"];
96
 
bitsyntax(Config) when list(Config) ->
 
96
bitsyntax(Config) when is_list(Config) ->
97
97
    ?line setup(Config),
98
98
    ?line [{'_',[],
99
99
            [<<0,27,0,27>>]}] =
131
131
    [];
132
132
record_defaults(doc) ->
133
133
    ["Tests that record defaults works"];
134
 
record_defaults(Config) when list(Config) ->
 
134
record_defaults(Config) when is_list(Config) ->
135
135
    ?line setup(Config),    
136
136
    ?line [{{<<27>>,{a,5,'$1',hej,hej}},
137
137
            [],
146
146
    [];
147
147
basic_ets(doc) ->
148
148
    ["Tests basic ets:fun2ms"];
149
 
basic_ets(Config) when list(Config) ->
 
149
basic_ets(Config) when is_list(Config) ->
150
150
    ?line setup(Config),
151
151
    ?line [{{a,b},[],[true]}] = compile_and_run(
152
152
                                  <<"ets:fun2ms(fun({a,b}) -> true end)">>),
167
167
    [];
168
168
basic_dbg(doc) ->
169
169
    ["Tests basic ets:fun2ms"];
170
 
basic_dbg(Config) when list(Config) ->
 
170
basic_dbg(Config) when is_list(Config) ->
171
171
    ?line setup(Config),
172
172
    ?line [{[a,b],[],[{message,banan},{return_trace}]}] =
173
173
        compile_and_run(<<"dbg:fun2ms(fun([a,b]) -> message(banan), ",
186
186
    [];
187
187
from_shell(doc) ->
188
188
    ["Test calling of ets/dbg:fun2ms from the shell"]; 
189
 
from_shell(Config) when list(Config) ->
 
189
from_shell(Config) when is_list(Config) ->
190
190
    ?line setup(Config),
191
191
    ?line Fun = do_eval("fun({a,b}) -> true end"),
192
192
    ?line [{{a,b},[],[true]}] = apply(ets,fun2ms,[Fun]),
203
203
    [];
204
204
records(doc) ->
205
205
    ["Tests expansion of records in fun2ms"];
206
 
records(Config) when list(Config) ->
 
206
records(Config) when is_list(Config) ->
207
207
    ?line setup(Config),
208
208
    ?line RD = <<"-record(t, {"
209
209
                     "t1 = [],"
253
253
    [];
254
254
record_index(doc) ->
255
255
    ["Tests expansion of records in fun2ms, part 2"];
256
 
record_index(Config) when list(Config) ->
 
256
record_index(Config) when is_list(Config) ->
257
257
    ?line setup(Config),
258
258
    ?line RD = <<"-record(a,{a,b}).">>,
259
259
    ?line [{{2},[],[true]}] = compile_and_run(RD,
268
268
    [];
269
269
top_match(doc) ->
270
270
    ["Tests matching on top level in head to give alias for object()"];
271
 
top_match(Config) when list(Config) ->
 
271
top_match(Config) when is_list(Config) ->
272
272
    ?line setup(Config),
273
273
    ?line RD = <<"-record(a,{a,b}).">>,
274
274
    ?line [{{a,3,'_'},[],['$_']}] = 
295
295
    [];
296
296
multipass(doc) ->
297
297
    ["Tests that multi-defined fields in records give errors."];
298
 
multipass(Config) when list(Config) ->
 
298
multipass(Config) when is_list(Config) ->
299
299
    ?line setup(Config),
300
300
    ?line RD = <<"-record(a,{a,b}).">>,
301
301
    ?line expect_failure(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,a=3} end)">>), 
319
319
    [];
320
320
old_guards(doc) ->
321
321
    ["Tests that old type tests in guards are translated"];
322
 
old_guards(Config) when list(Config) ->
 
322
old_guards(Config) when is_list(Config) ->
323
323
    ?line setup(Config),
324
324
    Tests = [
325
325
             {atom,is_atom},
382
382
autoimported(doc) ->
383
383
    ["Tests use of autoimported bif's used like erlang:'+'(A,B) in guards"
384
384
     " and body."];
385
 
autoimported(Config) when list(Config) ->
 
385
autoimported(Config) when is_list(Config) ->
386
386
    ?line setup(Config),
387
387
    Allowed = [
388
388
               {abs,1},
582
582
    [];
583
583
float_1_function(doc) ->
584
584
    ["OTP-5297. The function float/1."];
585
 
float_1_function(Config) when list(Config) ->
 
585
float_1_function(Config) when is_list(Config) ->
586
586
    ?line setup(Config),
587
587
    RunMS = fun(L, MS) -> 
588
588
                    ets:match_spec_run(L, ets:match_spec_compile(MS))