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

« back to all changes in this revision

Viewing changes to lib/debugger/test/bs_construct_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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2000-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
-module(bs_construct_SUITE).
 
21
 
 
22
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2,
 
23
         init_per_testcase/2,end_per_testcase/2,
 
24
         init_per_suite/1,end_per_suite/1,
 
25
         test1/1, test2/1, test3/1, test4/1, test5/1, testf/1, not_used/1, in_guard/1,
 
26
         coerce_to_float/1]).
 
27
 
 
28
-include_lib("test_server/include/test_server.hrl").
 
29
 
 
30
suite() -> [{ct_hooks,[ts_install_cth]}].
 
31
 
 
32
all() -> 
 
33
    cases().
 
34
 
 
35
groups() -> 
 
36
    [].
 
37
 
 
38
init_per_group(_GroupName, Config) ->
 
39
    Config.
 
40
 
 
41
end_per_group(_GroupName, Config) ->
 
42
    Config.
 
43
 
 
44
 
 
45
cases() -> 
 
46
    [test1, test2, test3, test4, test5, testf, not_used,
 
47
     in_guard, coerce_to_float].
 
48
 
 
49
init_per_testcase(_Case, Config) ->
 
50
    test_lib:interpret(?MODULE),
 
51
    Dog = test_server:timetrap(?t:minutes(1)),
 
52
    [{watchdog,Dog}|Config].
 
53
 
 
54
end_per_testcase(_Case, Config) ->
 
55
    Dog = ?config(watchdog, Config),
 
56
    ?t:timetrap_cancel(Dog),
 
57
    ok.
 
58
 
 
59
init_per_suite(Config) when is_list(Config) ->
 
60
    ?line test_lib:interpret(?MODULE),
 
61
    ?line true = lists:member(?MODULE, int:interpreted()),
 
62
    Config.
 
63
 
 
64
end_per_suite(Config) when is_list(Config) ->
 
65
    ok.
 
66
 
 
67
big(1) ->
 
68
    57285702734876389752897683.
 
69
 
 
70
i(X) -> X.
 
71
 
 
72
r(L) ->
 
73
    lists:reverse(L).
 
74
 
 
75
-define(T(B, L), {B, ??B, L}).
 
76
-define(N(B), {B, ??B, unknown}).
 
77
 
 
78
-define(FAIL(Expr), ?line {'EXIT',{badarg,_}} = (catch Expr)).
 
79
 
 
80
l(I_13, I_big1) ->
 
81
    [
 
82
     ?T(<<-43>>,
 
83
        [256-43]),
 
84
     ?T(<<56>>,
 
85
        [56]),
 
86
     ?T(<<1,2>>,
 
87
        [1, 2]),
 
88
     ?T(<<4:4, 7:4>>,
 
89
        [4*16+7]),
 
90
     ?T(<<777:16/big>>,
 
91
        [3, 9]),
 
92
     ?T(<<777:16/little>>,
 
93
        [9, 3]),
 
94
     ?T(<<0.0:32/float>>,
 
95
        [0,0,0,0]),
 
96
     ?T(<<0.125:32/float>>,
 
97
        [62,0,0,0]),
 
98
     ?T(<<0.125:32/little-float>>,
 
99
        [0,0,0,62]),
 
100
     ?T(<<I_big1:32>>,
 
101
        [138, 99, 0, 147]),
 
102
     ?T(<<57285702734876389752897684:32>>,
 
103
        [138, 99, 0, 148]),
 
104
     ?T(<<I_big1:32/little>>,
 
105
        r([138, 99, 0, 147])),
 
106
     ?T(<<-1:17/unit:8>>,
 
107
        lists:duplicate(17, 255)),
 
108
 
 
109
     ?T(<<I_13>>,
 
110
        [13]),
 
111
 
 
112
     ?T(<<4:8/unit:2,5:2/unit:8>>,
 
113
        [0, 4, 0, 5]),
 
114
 
 
115
     ?T(<<1:1, 0:6, 1:1>>,
 
116
        [129]),
 
117
     ?T(<<1:1/little, 0:6/little, 1:1/little>>,
 
118
        [129]),
 
119
 
 
120
     ?T(<<<<1,2>>/binary>>,
 
121
        [1, 2]),
 
122
     ?T(<<<<1,2>>:1/binary>>,
 
123
        [1]),
 
124
     ?T(<<4,3,<<1,2>>:1/binary>>,
 
125
        [4,3,1]),
 
126
 
 
127
     ?T(<<(256*45+47)>>,
 
128
        [47]),
 
129
 
 
130
     ?T(<<57:0>>,
 
131
        []),
 
132
 
 
133
     ?T(<<"apa">>,
 
134
        "apa"),
 
135
 
 
136
     ?T(<<1:3,"string",9:5>>,
 
137
        [46,110,142,77,45,204,233]),
 
138
 
 
139
     ?T(<<>>,
 
140
        []),
 
141
 
 
142
     ?T(<<37.98:64/native-float>>,
 
143
        native_3798()),
 
144
 
 
145
     ?T(<<32978297842987249827298387697777669766334937:128/native-integer>>,
 
146
        native_bignum())
 
147
 
 
148
     ].
 
149
 
 
150
native_3798() ->
 
151
    case <<1:16/native>> of
 
152
        <<0,1>> -> [64,66,253,112,163,215,10,61];
 
153
        <<1,0>> -> [61,10,215,163,112,253,66,64]
 
154
    end.
 
155
 
 
156
native_bignum() ->
 
157
    case <<1:16/native>> of
 
158
        <<0,1>> -> [129,205,18,177,1,213,170,101,39,231,109,128,176,11,73,217];
 
159
        <<1,0>> -> [217,73,11,176,128,109,231,39,101,170,213,1,177,18,205,129]
 
160
    end.
 
161
 
 
162
evaluate(Str, Vars) ->
 
163
    {ok,Tokens,_} =
 
164
        erl_scan:string(Str ++ " . "),
 
165
    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
166
    case erl_eval:expr(Expr, Vars) of
 
167
        {value, Result, _} ->
 
168
            Result
 
169
    end.
 
170
 
 
171
eval_list([], _Vars) ->
 
172
    [];
 
173
eval_list([{C_bin, Str, Bytes} | Rest], Vars) ->
 
174
    case catch evaluate(Str, Vars) of
 
175
        {'EXIT', Error} ->
 
176
            io:format("Evaluation error: ~p, ~p, ~p~n", [Str, Vars, Error]),
 
177
            exit(Error);
 
178
        E_bin ->
 
179
            [{C_bin, E_bin, Str, Bytes} | eval_list(Rest, Vars)]
 
180
    end.
 
181
 
 
182
one_test({C_bin, E_bin, Str, Bytes}) when list(Bytes) ->
 
183
    io:format("  ~s, ~p~n", [Str, Bytes]),
 
184
    Bin = list_to_binary(Bytes),
 
185
    if
 
186
        C_bin == Bin ->
 
187
            ok;
 
188
        true ->
 
189
            io:format("ERROR: Compiled: ~p. Expected ~p. Got ~p.~n",
 
190
                      [Str, Bytes, binary_to_list(C_bin)]),
 
191
            test_server:fail(comp)
 
192
    end,
 
193
    if
 
194
        E_bin == Bin ->
 
195
            ok;
 
196
        true ->
 
197
            io:format("ERROR: Interpreted: ~p. Expected ~p. Got ~p.~n",
 
198
                      [Str, Bytes, binary_to_list(E_bin)]),
 
199
            test_server:fail(comp)
 
200
    end;
 
201
one_test({C_bin, E_bin, Str, Result}) ->
 
202
    io:format("  ~s ~p~n", [Str, C_bin]),
 
203
    if
 
204
        C_bin == E_bin ->
 
205
            ok;
 
206
        true ->
 
207
            Arbitrary = case Result of
 
208
                            unknown ->
 
209
                                size(C_bin);
 
210
                            _ ->
 
211
                                Result
 
212
                        end,
 
213
            case equal_lists(binary_to_list(C_bin),
 
214
                             binary_to_list(E_bin),
 
215
                             Arbitrary) of
 
216
                false ->
 
217
                    io:format("ERROR: Compiled not equal to interpreted:"
 
218
                              "~n ~p, ~p.~n",
 
219
                              [binary_to_list(C_bin), binary_to_list(E_bin)]),
 
220
                    test_server:fail(comp);
 
221
                0 ->
 
222
                    ok;
 
223
                %% For situations where the final bits may not matter, like
 
224
                %% for floats:
 
225
                N when integer(N) ->
 
226
                    io:format("Info: compiled and interpreted differ in the"
 
227
                              " last bytes:~n ~p, ~p.~n",
 
228
                              [binary_to_list(C_bin), binary_to_list(E_bin)]),
 
229
                    ok
 
230
            end
 
231
    end.
 
232
 
 
233
equal_lists([], [], _) ->
 
234
    0;
 
235
equal_lists([], _, _) ->
 
236
    false;
 
237
equal_lists(_, [], _) ->
 
238
    false;
 
239
equal_lists([A|AR], [A|BR], R) ->
 
240
    equal_lists(AR, BR, R);
 
241
equal_lists(A, B, R) ->
 
242
    if
 
243
        length(A) /= length(B) ->
 
244
            false;
 
245
        length(A) =< R ->
 
246
            R;
 
247
        true ->
 
248
            false
 
249
    end.
 
250
 
 
251
%%% Simple working cases
 
252
test1(suite) -> [];
 
253
test1(Config) when list(Config) ->
 
254
    ?line I_13 = i(13),
 
255
    ?line I_big1 = big(1),
 
256
    ?line Vars = [{'I_13', I_13},
 
257
                  {'I_big1', I_big1}],
 
258
    ?line lists:foreach(fun one_test/1, eval_list(l(I_13, I_big1), Vars)).
 
259
 
 
260
%%% Misc
 
261
 
 
262
%%% <<A:S, A:(N-S)>>
 
263
comp(N, A, S) ->
 
264
    M1 = (1 bsl S) - 1,
 
265
    M2 = (1 bsl (N-S)) - 1,
 
266
    [((A band M1) bsl (N-S)) bor (A band M2)].
 
267
 
 
268
gen(N, S, A) ->
 
269
    [?T(<<A:S, A:(N-S)>>, comp(N, A, S))].
 
270
 
 
271
gen_l(N, S, A) ->
 
272
    [?T(<<A:S/little, A:(N-S)/little>>, comp(N, A, S))].
 
273
 
 
274
test2(suite) -> [];
 
275
test2(Config) when list(Config) ->
 
276
    ?line test2(0, 8, 2#10101010101010101),
 
277
    ?line test2(0, 8, 2#1111111111).
 
278
 
 
279
test2(End, End, _) ->
 
280
    ok;
 
281
test2(I, End, A) ->
 
282
    test2(I, A),
 
283
    test2(I+1, End, A).
 
284
 
 
285
test2(S, A) ->
 
286
    N = 8,
 
287
    Vars = [{'A',A}, {'N',N}, {'S',S}],
 
288
    io:format("Vars: ~p\n", [Vars]),
 
289
    lists:foreach(fun one_test/1, eval_list(gen(N, S, A), Vars)),
 
290
    lists:foreach(fun one_test/1, eval_list(gen_l(N, S, A), Vars)).
 
291
 
 
292
%%% Tests without facit
 
293
 
 
294
t3() ->
 
295
    [?N(<<4711:13, 9876:13, 3:6>>),
 
296
     ?N(<<4.57:64/float>>),
 
297
     ?N(<<4.57:32/float>>),
 
298
 
 
299
     ?N(<<>>)
 
300
    ].
 
301
 
 
302
test3(suite) -> [];
 
303
test3(Config) when list(Config) ->
 
304
    ?line Vars = [],
 
305
    ?line lists:foreach(fun one_test/1, eval_list(t3(), Vars)).
 
306
 
 
307
gen_u(N, S, A) ->
 
308
    [?N(<<A:S, A:(N-S)>>)].
 
309
 
 
310
gen_u_l(N, S, A) ->
 
311
    [?N(<<A:S/little, A:(N-S)/little>>)].
 
312
 
 
313
test4(suite) -> [];
 
314
test4(Config) when list(Config) ->
 
315
    ?line test4(0, 16, 2#10101010101010101),
 
316
    ?line test4(0, 16, 2#1111111111).
 
317
 
 
318
test4(End, End, _) ->
 
319
    ok;
 
320
test4(I, End, A) ->
 
321
    test4(I, A),
 
322
    test4(I+1, End, A).
 
323
 
 
324
test4(S, A) ->
 
325
    N = 16,
 
326
    Vars = [{'A', A}, {'N', 16}, {'S', S}],
 
327
    lists:foreach(fun one_test/1, eval_list(gen_u(N, S, A), Vars)),
 
328
    lists:foreach(fun one_test/1, eval_list(gen_u_l(N, S, A), Vars)).
 
329
 
 
330
gen_b(N, S, A) ->
 
331
    [?T(<<A:S/binary-unit:1, A:(N-S)/binary-unit:1>>,
 
332
        binary_to_list(<<A:S/binary-unit:1, A:(N-S)/binary-unit:1>>))].
 
333
 
 
334
test5(suite) -> [];
 
335
test5(doc) -> ["OTP-3995"];
 
336
test5(Config) when list(Config) ->
 
337
    ?line test5(0, 8, <<73>>),
 
338
    ?line test5(0, 8, <<68>>).
 
339
 
 
340
test5(End, End, _) ->
 
341
    ok;
 
342
test5(I, End, A) ->
 
343
    test5(I, A),
 
344
    test5(I+1, End, A).
 
345
 
 
346
test5(S, A) ->
 
347
    N = 8,
 
348
    Vars = [{'A', A}, {'N', 8}, {'S', S}],
 
349
    lists:foreach(fun one_test/1, eval_list(gen_b(N, S, A), Vars)).
 
350
 
 
351
%%% Failure cases
 
352
testf(suite) -> [];
 
353
testf(Config) when list(Config) ->
 
354
    ?FAIL(<<3.14>>),
 
355
    ?FAIL(<<<<1,2>>>>),
 
356
 
 
357
    ?FAIL(<<2.71/binary>>),
 
358
    ?FAIL(<<24334/binary>>),
 
359
    ?FAIL(<<24334344294788947129487129487219847/binary>>),
 
360
 
 
361
    ?FAIL(<<<<1,2,3>>/float>>),
 
362
 
 
363
    %% Negative field widths.
 
364
    testf_1(-8, <<1,2,3,4,5>>),
 
365
 
 
366
    ?FAIL(<<42:(-16)>>),
 
367
    ?FAIL(<<3.14:(-8)/float>>),
 
368
    ?FAIL(<<<<23,56,0,2>>:(-16)/binary>>),
 
369
    ?FAIL(<<<<23,56,0,2>>:(2.5)/binary>>),
 
370
    ?FAIL(<<<<23,56,0,2>>:(anka)>>),
 
371
 
 
372
    ok.
 
373
 
 
374
testf_1(W, B) ->
 
375
    ?FAIL(<<42:W>>),
 
376
    ?FAIL(<<3.14:W/float>>),
 
377
    ?FAIL(<<B:W/binary>>).
 
378
 
 
379
not_used(doc) ->
 
380
    "Test that constructed binaries that are not used will still give an exception.";
 
381
not_used(Config) when is_list(Config) ->
 
382
    ?line ok = not_used1(3, <<"dum">>),
 
383
    ?line ?FAIL(not_used1(3, "dum")),
 
384
    ?line ?FAIL(not_used2(444, -2)),
 
385
    ?line ?FAIL(not_used2(444, anka)),
 
386
    ?line ?FAIL(not_used3(444)),
 
387
    ok.
 
388
 
 
389
not_used1(I, BinString) ->
 
390
    <<I:32,BinString/binary>>,
 
391
    ok.
 
392
 
 
393
not_used2(I, Sz) ->
 
394
    <<I:Sz>>,
 
395
    ok.
 
396
 
 
397
not_used3(I) ->
 
398
    <<I:(-8)>>,
 
399
    ok.
 
400
 
 
401
in_guard(Config) when list(Config) ->
 
402
    ?line 1 = in_guard(<<16#74ad:16>>, 16#e95, 5),
 
403
    ?line 2 = in_guard(<<16#3A,16#F7,"hello">>, 16#3AF7, <<"hello">>),
 
404
    ?line 3 = in_guard(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415),
 
405
    nope = in_guard(<<1>>, 42, b),
 
406
    nope = in_guard(<<1>>, a, b),
 
407
    nope = in_guard(<<1,2>>, 1, 1),
 
408
    nope = in_guard(<<4,5>>, 1, 2.71),
 
409
    nope = in_guard(<<4,5>>, 1, <<12,13>>),
 
410
    ok.
 
411
 
 
412
in_guard(Bin, A, B) when <<A:13,B:3>> == Bin -> 1;
 
413
in_guard(Bin, A, B) when <<A:16,B/binary>> == Bin -> 2;
 
414
in_guard(Bin, A, B) when <<A:14,B/float,3:2>> == Bin -> 3;
 
415
in_guard(Bin, A, B) when {a,b,<<A:14,B/float,3:2>>} == Bin -> cant_happen;
 
416
in_guard(_, _, _) -> nope.
 
417
 
 
418
-define(COF(Int0),
 
419
        ?line (fun(Int) ->
 
420
                       true = <<Int:32/float>> =:= <<(float(Int)):32/float>>,
 
421
                       true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
 
422
                           end)(nonliteral(Int0)),
 
423
        ?line true = <<Int0:32/float>> =:= <<(float(Int0)):32/float>>,
 
424
        ?line true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>).
 
425
 
 
426
-define(COF64(Int0),
 
427
        ?line (fun(Int) ->
 
428
                       true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
 
429
                           end)(nonliteral(Int0)),
 
430
        ?line true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>).
 
431
 
 
432
nonliteral(X) -> X.
 
433
 
 
434
coerce_to_float(Config) when list(Config) ->
 
435
    ?COF(0),
 
436
    ?COF(-1),
 
437
    ?COF(1),
 
438
    ?COF(42),
 
439
    ?COF(255),
 
440
    ?COF(-255),
 
441
    ?COF(38474),
 
442
    ?COF(387498738948729893849444444443),
 
443
    ?COF(-37489378937773899999999999999993),
 
444
    ?COF64(298748888888888888888888888883478264866528467367364766666666666666663),
 
445
    ?COF64(-367546729879999999999947826486652846736736476555566666663),
 
446
    ok.