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

« back to all changes in this revision

Viewing changes to lib/tools/test/cover_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 2001-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2001-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
18
18
%%
19
19
-module(cover_SUITE).
20
20
 
21
 
-export([all/1]).
 
21
-export([all/0, init_per_testcase/2, end_per_testcase/2,
 
22
         suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
23
         init_per_group/2,end_per_group/2]).
 
24
 
22
25
-export([start/1, compile/1, analyse/1, misc/1, stop/1, 
23
26
         distribution/1, export_import/1,
24
27
         otp_5031/1, eif/1, otp_5305/1, otp_5418/1, otp_6115/1, otp_7095/1,
25
28
         otp_8188/1, otp_8270/1, otp_8273/1, otp_8340/1]).
26
29
 
27
 
-include("test_server.hrl").
 
30
-include_lib("test_server/include/test_server.hrl").
28
31
 
29
32
%%----------------------------------------------------------------------
30
33
%% The following directory structure is assumed:
37
40
%%                                             y
38
41
%%----------------------------------------------------------------------
39
42
 
40
 
all(suite) -> 
 
43
suite() -> [{ct_hooks,[ts_install_cth]}].
 
44
 
 
45
all() -> 
41
46
    case whereis(cover_server) of
42
47
        undefined ->
43
48
            [start, compile, analyse, misc, stop, distribution,
44
 
             export_import,
45
 
             otp_5031, eif, otp_5305, otp_5418, otp_6115, otp_7095,
46
 
             otp_8188, otp_8270, otp_8273, otp_8340];
 
49
             export_import, otp_5031, eif, otp_5305, otp_5418,
 
50
             otp_6115, otp_7095, otp_8188, otp_8270, otp_8273,
 
51
             otp_8340];
47
52
        _pid ->
48
 
            {skip,"It looks like the test server is running cover. "
49
 
                  "Can't run cover test."}
 
53
            {skip,
 
54
             "It looks like the test server is running "
 
55
             "cover. Can't run cover test."}
50
56
    end.
51
57
 
 
58
groups() -> 
 
59
    [].
 
60
 
 
61
init_per_suite(Config) ->
 
62
    Config.
 
63
 
 
64
end_per_suite(_Config) ->
 
65
    ok.
 
66
 
 
67
init_per_group(_GroupName, Config) ->
 
68
    Config.
 
69
 
 
70
end_per_group(_GroupName, Config) ->
 
71
    Config.
 
72
 
 
73
init_per_testcase(TC, Config) when TC =:= misc; 
 
74
                                   TC =:= compile; 
 
75
                                   TC =:= analyse;
 
76
                                   TC =:= distribution;
 
77
                                   TC =:= otp_5031;
 
78
                                   TC =:= stop ->
 
79
    case code:which(crypto) of
 
80
        Path when is_list(Path) ->
 
81
            init_per_testcase(dummy_tc, Config);
 
82
        _Else ->
 
83
            {skip, "No crypto file to test with"}
 
84
    end;
 
85
init_per_testcase(_TestCase, Config) ->
 
86
    Config.
 
87
 
 
88
end_per_testcase(_TestCase, _Config) ->
 
89
    %cover:stop(),
 
90
    ok.
 
91
 
52
92
start(suite) -> [];
53
93
start(Config) when is_list(Config) ->
54
94
    ?line ok = file:set_cwd(?config(data_dir, Config)),
90
130
    ?line {ok,_} = compile:file(x),
91
131
    ?line {ok,_} = compile:file("d/y",[debug_info,{outdir,"d"},report]),
92
132
    ?line Key = "A Krypto Key",
93
 
    ?line {ok,_} = compile:file(crypt, [debug_info,{debug_info_key,Key},report]),
 
133
    CryptoWorks = crypto_works(),
 
134
    case CryptoWorks of
 
135
        false ->
 
136
            {ok,_} = compile:file(crypt, [debug_info,report]),
 
137
            {ok,crypt} = cover:compile_beam("crypt.beam");
 
138
        true ->
 
139
            {ok,_} = compile:file(crypt, [{debug_info_key,Key},report]),
 
140
            {error,{encrypted_abstract_code,_}} =
 
141
                cover:compile_beam("crypt.beam"),
 
142
            ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)),
 
143
            {ok,crypt} = cover:compile_beam("crypt.beam")
 
144
    end,
94
145
    ?line {ok,v} = cover:compile_beam(v),
95
146
    ?line {ok,w} = cover:compile_beam("w.beam"),
96
 
    ?line {error,{encrypted_abstract_code,_}} =
97
 
        cover:compile_beam("crypt.beam"),
98
 
    ?line ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)),
99
 
    ?line {ok,crypt} = cover:compile_beam("crypt.beam"),
100
147
    ?line {error,{no_abstract_code,"./x.beam"}} = cover:compile_beam(x),
101
148
    ?line {error,{already_cover_compiled,no_beam_found,a}}=cover:compile_beam(a),
102
149
    ?line {error,non_existing} = cover:compile_beam(z),
108
155
    ?line Files = lsfiles(),
109
156
    ?line remove(files(Files, ".beam")).
110
157
 
 
158
crypto_works() ->
 
159
    try crypto:start() of
 
160
        {error,{already_started,crypto}} -> true;
 
161
        ok -> true
 
162
    catch
 
163
        error:_ ->
 
164
            false
 
165
    end.
 
166
 
111
167
simple_crypto_fun(Key) ->
112
168
    fun(init) -> ok;
113
169
       ({debug_info, des3_cbc, crypt, _}) -> Key
331
387
 
332
388
    %% Check that stop() unloads on all nodes
333
389
    ?line ok = cover:stop(),
 
390
    ?line timer:sleep(100), %% Give nodes time to unload on slow machines.
334
391
    ?line LocalBeam = code:which(f),
335
392
    ?line N2Beam = rpc:call(N2,code,which,[f]),
336
393
    ?line true = is_unloaded(LocalBeam),
354
411
export_import(Config) when is_list(Config) ->
355
412
    ?line DataDir = ?config(data_dir, Config),
356
413
    ?line ok = file:set_cwd(DataDir),
 
414
    ?line PortCount = length(erlang:ports()),
357
415
 
358
416
    %% Export one module
359
417
    ?line {ok,f} = cover:compile(f),
381
439
    ?line {ok,a} = cover:compile(a),
382
440
    ?line ?t:capture_start(),
383
441
    ?line ok = cover:export("all_exported"),
384
 
    ?line [Text2] = ?t:capture_get(),
385
 
    ?line "Export includes data from imported files"++_ = lists:flatten(Text2),
 
442
    ?line [] = ?t:capture_get(),
 
443
%    ?line "Export includes data from imported files"++_ = lists:flatten(Text2),
386
444
    ?line ?t:capture_stop(),
387
445
    ?line ok = cover:stop(),
388
446
    ?line ok = cover:import("all_exported"),
443
501
    ?line ?t:capture_stop(),
444
502
    ?line check_f_calls(1,0),
445
503
 
 
504
    %% Check no raw files are left open
 
505
    ?line PortCount = length(erlang:ports()),
 
506
 
446
507
    %% Cleanup
447
508
    ?line ok = cover:stop(),
448
509
    ?line Files = lsfiles(),
538
599
    %% called -- running cover compiled code when there is no cover
539
600
    %% server and thus no ets tables to bump counters in, makes no
540
601
    %% sense.
541
 
    ?line Pid1 = f1:start_fail(),
542
 
 
543
 
    %% If f1 is cover compiled, a process P is started with a
544
 
    %% reference to the fun created in start_ok/0, and
545
 
    %% cover:stop() is called, then P should survive.
546
 
    %% This is because (the fun held by) P always references the current
547
 
    %% version of the module, and is thus not affected by the cover
548
 
    %% compiled version being unloaded.
549
 
    ?line Pid2 = f1:start_ok(),
 
602
    Pid1 = f1:start_a(),
 
603
    Pid2 = f1:start_b(),
550
604
 
551
605
    %% Now stop cover
552
606
    ?line cover:stop(),
553
607
    
554
 
    %% Ensure that f1 is loaded (and not cover compiled), that Pid1
555
 
    %% is dead and Pid2 is alive, but with no reference to old code
 
608
    %% Ensure that f1 is loaded (and not cover compiled), and that
 
609
    %% both Pid1 and Pid2 are dead.
556
610
    case code:which(f1) of
557
611
        Beam when is_list(Beam) ->
558
612
            ok;
563
617
        undefined ->
564
618
            ok;
565
619
        _PI1 ->
566
 
            RefToOldP = erlang:check_process_code(Pid1, f1),
567
 
            ?line ?t:fail({"Pid1 still alive", RefToOldP})
 
620
            RefToOldP1 = erlang:check_process_code(Pid1, f1),
 
621
            ?t:fail({"Pid1 still alive", RefToOldP1})
568
622
    end,
569
623
    case process_info(Pid2) of
570
 
        PI2 when is_list(PI2) ->
571
 
            case erlang:check_process_code(Pid2, f2) of
572
 
                false ->
573
 
                    ok;
574
 
                true ->
575
 
                    ?line ?t:fail("Pid2 has ref to old code")
576
 
            end;
577
624
        undefined ->
578
 
            ?line ?t:fail("Pid2 has died")
 
625
            ok;
 
626
        _PI2 ->
 
627
            RefToOldP2 = erlang:check_process_code(Pid1, f2),
 
628
            ?t:fail({"Pid2 still alive", RefToOldP2})
579
629
    end,
580
630
 
581
631
    ?line file:set_cwd(CWD),