~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to erts/emulator/test/match_spec_SUITE.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
5
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
19
19
 
20
20
-module(match_spec_SUITE).
21
21
 
22
 
-export([all/1, not_run/1]).
 
22
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
23
         init_per_group/2,end_per_group/2, not_run/1]).
23
24
-export([test_1/1, test_2/1, test_3/1, bad_match_spec_bin/1,
24
25
         trace_control_word/1, silent/1, silent_no_ms/1, 
25
26
         ms_trace2/1, ms_trace3/1, boxed_and_small/1,
26
27
         destructive_in_test_bif/1, guard_exceptions/1,
27
28
         unary_plus/1, unary_minus/1, moving_labels/1]).
28
29
-export([fpe/1]).
 
30
-export([otp_9422/1]).
29
31
 
30
 
-export([runner/2]).
 
32
-export([runner/2, loop_runner/3]).
31
33
-export([f1/1, f2/2, f3/2, fn/1, fn/2, fn/3]).
32
34
-export([do_boxed_and_small/0]).
33
35
 
34
36
% This test suite assumes that tracing in general works. What we test is
35
37
% the match spec functionality.
36
38
 
37
 
-include("test_server.hrl").
 
39
-include_lib("test_server/include/test_server.hrl").
38
40
 
39
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
41
-export([init_per_testcase/2, end_per_testcase/2]).
40
42
 
41
43
init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
42
44
    Dog=?t:timetrap(?t:seconds(10)),
43
45
    [{watchdog, Dog}|Config].
44
46
 
45
 
fin_per_testcase(_Func, Config) ->
 
47
end_per_testcase(_Func, Config) ->
46
48
    Dog=?config(watchdog, Config),
47
49
    ?t:timetrap_cancel(Dog).
48
50
 
49
51
 
50
 
all(suite) ->
51
 
    case test_server:is_native(?MODULE) of
52
 
        false -> [test_1, test_2, test_3, bad_match_spec_bin,
53
 
                  trace_control_word, silent, silent_no_ms, 
54
 
                  ms_trace2, ms_trace3, boxed_and_small,
55
 
                  destructive_in_test_bif, guard_exceptions,
56
 
                  unary_plus, unary_minus, fpe, moving_labels];
57
 
        true  -> [not_run]
 
52
suite() -> [{ct_hooks,[ts_install_cth]}].
 
53
 
 
54
all() -> 
 
55
    case test_server:is_native(match_spec_SUITE) of
 
56
        false ->
 
57
            [test_1, test_2, test_3, bad_match_spec_bin,
 
58
             trace_control_word, silent, silent_no_ms, ms_trace2,
 
59
             ms_trace3, boxed_and_small, destructive_in_test_bif,
 
60
             guard_exceptions, unary_plus, unary_minus, fpe,
 
61
             moving_labels,
 
62
             otp_9422];
 
63
        true -> [not_run]
58
64
    end.
59
65
 
 
66
groups() -> 
 
67
    [].
 
68
 
 
69
init_per_suite(Config) ->
 
70
    Config.
 
71
 
 
72
end_per_suite(_Config) ->
 
73
    ok.
 
74
 
 
75
init_per_group(_GroupName, Config) ->
 
76
    Config.
 
77
 
 
78
end_per_group(_GroupName, Config) ->
 
79
        Config.
 
80
 
 
81
 
60
82
not_run(Config) when is_list(Config) ->
61
83
    {skipped, "Native Code"}.
62
84
 
188
210
    ?line collect(P1, [{trace, P1, call, {?MODULE, f2, [a, b]}, [true]}]),
189
211
    ?line ok.
190
212
 
 
213
otp_9422(doc) -> [];
 
214
otp_9422(Config) when is_list(Config) ->
 
215
    Laps = 1000,
 
216
    ?line Fun1 = fun() -> otp_9422_tracee() end,
 
217
    ?line P1 = spawn_link(?MODULE, loop_runner, [self(), Fun1, Laps]),
 
218
    io:format("spawned ~p as tracee\n", [P1]),
 
219
 
 
220
    ?line erlang:trace(P1, true, [call, silent]),
 
221
 
 
222
    ?line Fun2 = fun() -> otp_9422_trace_changer() end,
 
223
    ?line P2 = spawn_link(?MODULE, loop_runner, [self(), Fun2, Laps]),
 
224
    io:format("spawned ~p as trace_changer\n", [P2]),
 
225
 
 
226
    start_collect(P1),
 
227
    start_collect(P2),
 
228
 
 
229
    %%receive after 10*1000 -> ok end,
 
230
 
 
231
    stop_collect(P1),
 
232
    stop_collect(P2),
 
233
    ok.
 
234
    
 
235
otp_9422_tracee() ->
 
236
    ?MODULE:f1(a),
 
237
    ?MODULE:f1(b),
 
238
    ?MODULE:f1(c).
 
239
 
 
240
otp_9422_trace_changer() ->
 
241
    Pat1 = [{[a], [], [{enable_trace, arity}]}],
 
242
    ?line erlang:trace_pattern({?MODULE, f1, 1}, Pat1),
 
243
    Pat2 = [{[b], [], [{disable_trace, arity}]}],
 
244
    ?line erlang:trace_pattern({?MODULE, f1, 1}, Pat2).
 
245
 
 
246
    
 
247
    
 
248
 
 
249
 
191
250
bad_match_spec_bin(Config) when is_list(Config) ->
192
251
    {'EXIT',{badarg,_}} = (catch ets:match_spec_run([1], <<>>)),
193
252
    B0 = <<1,2>>,
345
404
            fun () -> 
346
405
                    ?MODULE:f1(a),
347
406
                    ?MODULE:f2(b, c),
348
 
                    erlang:integer_to_list(id(1)),
 
407
                    _ = erlang:integer_to_list(id(1)),
349
408
                    ?MODULE:f3(d, e),
350
409
                    ?MODULE:f1(start),
351
410
                    ?MODULE:f2(f, g),
352
 
                    erlang:integer_to_list(id(2)),
 
411
                    _ = erlang:integer_to_list(id(2)),
353
412
                    ?MODULE:f3(h, i),
354
413
                    ?MODULE:f1(stop),
355
414
                    ?MODULE:f2(j, k),
356
 
                    erlang:integer_to_list(id(3)),
 
415
                    _ = erlang:integer_to_list(id(3)),
357
416
                    ?MODULE:f3(l, m)
358
417
            end,
359
418
            fun (Tracee) ->
393
452
            fun () -> 
394
453
                    ?MODULE:f1(a),
395
454
                    ?MODULE:f2(b, c),
396
 
                    erlang:integer_to_list(id(1)),
 
455
                    _ = erlang:integer_to_list(id(1)),
397
456
                    ?MODULE:f3(d, e),
398
457
                    ?MODULE:f1(start),
399
458
                    ?MODULE:f2(f, g),
400
 
                    erlang:integer_to_list(id(2)),
 
459
                    _ = erlang:integer_to_list(id(2)),
401
460
                    ?MODULE:f3(h, i),
402
461
                    ?MODULE:f1(stop),
403
462
                    ?MODULE:f2(j, k),
404
 
                    erlang:integer_to_list(id(3)),
 
463
                    _ = erlang:integer_to_list(id(3)),
405
464
                    ?MODULE:f3(l, m)
406
465
            end,
407
466
            fun (Tracee) ->
455
514
            fun () -> 
456
515
                    ?MODULE:f1(a),
457
516
                    ?MODULE:f2(b, c),
458
 
                    erlang:integer_to_list(id(1)),
 
517
                    _ = erlang:integer_to_list(id(1)),
459
518
                    ?MODULE:f3(d, e),
460
519
                    fn([all], [call,return_to,{tracer,Tracer}]),
461
520
                    ?MODULE:f1(f),
462
521
                    f2(g, h),
463
522
                    f1(i),
464
 
                    erlang:integer_to_list(id(2)),
 
523
                    _ = erlang:integer_to_list(id(2)),
465
524
                    ?MODULE:f3(j, k),
466
525
                    fn([call,return_to], []),
467
526
                    ?MODULE:f1(l),
468
527
                    ?MODULE:f2(m, n),
469
 
                    erlang:integer_to_list(id(3)),
 
528
                    _ = erlang:integer_to_list(id(3)),
470
529
                    ?MODULE:f3(o, p)
471
530
            end,
472
531
            fun (Tracee) ->
551
610
                    register(TraceeName, self()),
552
611
                    ?MODULE:f1(a),
553
612
                    ?MODULE:f2(b, c),
554
 
                    erlang:integer_to_list(id(1)),
 
613
                    _ = erlang:integer_to_list(id(1)),
555
614
                    ?MODULE:f3(d, e),
556
615
                    Controller ! {self(),Tag,start},
557
616
                    receive {Controller,Tag,started} -> ok end,
558
617
                    ?MODULE:f1(f),
559
618
                    f2(g, h),
560
619
                    f1(i),
561
 
                    erlang:integer_to_list(id(2)),
 
620
                    _ = erlang:integer_to_list(id(2)),
562
621
                    ?MODULE:f3(j, k),
563
622
                    Controller ! {self(),Tag,stop_1},
564
623
                    receive {Controller,Tag,stopped_1} -> ok end,
565
624
                    ?MODULE:f1(l),
566
625
                    ?MODULE:f2(m, n),
567
 
                    erlang:integer_to_list(id(3)),
 
626
                    _ = erlang:integer_to_list(id(3)),
568
627
                    ?MODULE:f3(o, p),
569
628
                    Controller ! {self(),Tag,stop_2},
570
629
                    receive {Controller,Tag,stopped_2} -> ok end,
571
630
                    ?MODULE:f1(q),
572
631
                    ?MODULE:f2(r, s),
573
 
                    erlang:integer_to_list(id(4)),
 
632
                    _ = erlang:integer_to_list(id(4)),
574
633
                    ?MODULE:f3(t, u)
575
634
            end,
576
635
            
912
971
            Collector ! {gone, self()}
913
972
    end.
914
973
 
 
974
loop_runner(Collector, Fun, Laps) ->
 
975
    receive
 
976
        {go, Collector} ->
 
977
            go
 
978
    end,
 
979
    loop_runner_cont(Collector, Fun, 0, Laps).
 
980
 
 
981
loop_runner_cont(_Collector, _Fun, Laps, Laps) ->
 
982
    receive
 
983
        {done, Collector} ->
 
984
            io:format("loop_runner ~p exit after ~p laps\n", [self(), Laps]),
 
985
            Collector ! {gone, self()}
 
986
    end;
 
987
loop_runner_cont(Collector, Fun, N, Laps) ->
 
988
    Fun(),
 
989
    loop_runner_cont(Collector, Fun, N+1, Laps).
 
990
 
 
991
 
915
992
f1(X) ->
916
993
    {X}.
917
994