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

« back to all changes in this revision

Viewing changes to lib/tools/test/xref_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 2000-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2000-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
29
29
-define(privdir, "xref_SUITE_priv").
30
30
-define(copydir, "xref_SUITE_priv/datacopy").
31
31
-else.
32
 
-include("test_server.hrl").
 
32
-include_lib("test_server/include/test_server.hrl").
33
33
-define(format(S, A), ok).
34
34
-define(datadir, ?config(data_dir, Conf)).
35
35
-define(privdir, ?config(priv_dir, Conf)).
36
36
-define(copydir, ?config(copy_dir, Conf)).
37
37
-endif.
38
38
 
39
 
-export([all/1, init/1, fini/1]).
 
39
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
40
         init_per_group/2,end_per_group/2, init/1, fini/1]).
40
41
 
41
 
-export([xref/1,
 
42
-export([
42
43
         addrem/1, convert/1, intergraph/1, lines/1, loops/1,
43
44
         no_data/1, modules/1]).
44
45
 
45
 
-export([files/1,
 
46
-export([
46
47
         add/1, default/1, info/1, lib/1, read/1, read2/1, remove/1,
47
48
         replace/1, update/1, deprecated/1, trycatch/1,
48
 
         abstract_modules/1, fun_mfa/1, qlc/1]).
 
49
         abstract_modules/1, fun_mfa/1, fun_mfa_r14/1,
 
50
         fun_mfa_vars/1, qlc/1]).
49
51
 
50
 
-export([analyses/1,
 
52
-export([
51
53
         analyze/1, basic/1, md/1, q/1, variables/1, unused_locals/1]).
52
54
 
53
 
-export([misc/1,
 
55
-export([
54
56
         format_error/1, otp_7423/1, otp_7831/1]).
55
57
 
56
58
-import(lists, [append/2, flatten/1, keysearch/3, member/2, sort/1, usort/1]).
59
61
        range/1, relation_to_family/1, set/1, to_external/1,
60
62
        union/2]).
61
63
 
62
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
64
-export([init_per_testcase/2, end_per_testcase/2]).
63
65
 
64
66
%% Checks some info counters of a server and some relations that should hold.
65
67
-export([check_count/1, check_state/1]).
68
70
 
69
71
-include_lib("tools/src/xref.hrl").
70
72
 
71
 
all(suite) ->
72
 
    {conf, init, [xref, files, analyses, misc], fini}.
 
73
suite() -> [{ct_hooks,[ts_install_cth]}].
 
74
 
 
75
all() -> 
 
76
    [{group, xref}, {group, files}, {group, analyses},
 
77
     {group, misc}].
 
78
 
 
79
groups() -> 
 
80
    [{xref, [],
 
81
      [addrem, convert, intergraph, lines, loops, no_data,
 
82
       modules]},
 
83
     {files, [],
 
84
      [add, default, info, lib, read, read2, remove, replace,
 
85
       update, deprecated, trycatch, abstract_modules, fun_mfa,
 
86
       fun_mfa_r14, fun_mfa_vars, qlc]},
 
87
     {analyses, [],
 
88
      [analyze, basic, md, q, variables, unused_locals]},
 
89
     {misc, [], [format_error, otp_7423, otp_7831]}].
 
90
 
 
91
init_per_suite(Config) ->
 
92
    init(Config).
 
93
 
 
94
end_per_suite(_Config) ->
 
95
    ok.
 
96
 
 
97
init_per_group(_GroupName, Config) ->
 
98
    Config.
 
99
 
 
100
end_per_group(_GroupName, Config) ->
 
101
    Config.
 
102
 
73
103
 
74
104
init(Conf) when is_list(Conf) ->
75
105
    DataDir = ?datadir,
91
121
    Dog=?t:timetrap(?t:minutes(2)),
92
122
    [{watchdog, Dog}|Config].
93
123
 
94
 
fin_per_testcase(_Case, _Config) ->
 
124
end_per_testcase(_Case, _Config) ->
95
125
    Dog=?config(watchdog, _Config),
96
126
    test_server:timetrap_cancel(Dog),
97
127
    ok.
98
128
 
99
 
xref(suite) ->
100
 
    [addrem, convert, intergraph, lines, loops, no_data, modules].
101
129
 
102
130
%% Seems a bit short...
103
131
addrem(suite) -> [];
680
708
    ?line ok = xref_base:delete(S),
681
709
    ok.
682
710
 
683
 
files(suite) ->
684
 
    [add, default, info, lib, read, read2, remove, replace, update,
685
 
     deprecated, trycatch, abstract_modules, fun_mfa, qlc].
686
711
 
687
712
add(suite) -> [];
688
713
add(doc) -> ["Add modules, applications, releases, directories"];
1747
1772
    ?line ok = file:delete(Beam),
1748
1773
    ok.
1749
1774
 
 
1775
%% Same as the previous test case, except that we use a BEAM file
 
1776
%% that was compiled by an R14 compiler to test backward compatibility.
 
1777
fun_mfa_r14(Conf) when is_list(Conf) ->
 
1778
    Dir = ?config(data_dir, Conf),
 
1779
    MFile = fname(Dir, "fun_mfa_r14"),
 
1780
 
 
1781
    A = fun_mfa_r14,
 
1782
    {ok, _} = xref:start(s),
 
1783
    {ok, A} = xref:add_module(s, MFile, {warnings,false}),
 
1784
    {ok, [{{{A,t,0},{'$M_EXPR','$F_EXPR',0}},[7]},
 
1785
          {{{A,t,0},{A,t,0}},[6]},
 
1786
          {{{A,t1,0},{'$M_EXPR','$F_EXPR',0}},[11]},
 
1787
          {{{A,t1,0},{A,t,0}},[10]},
 
1788
          {{{A,t2,0},{A,t,0}},[14]},
 
1789
          {{{A,t3,0},{A,t3,0}},[17]}]} =
 
1790
        xref:q(s, "(Lin) E"),
 
1791
 
 
1792
    ok = check_state(s),
 
1793
    xref:stop(s),
 
1794
 
 
1795
    ok.
 
1796
 
 
1797
%% fun M:F/A with varibles.
 
1798
fun_mfa_vars(Conf) when is_list(Conf) ->
 
1799
    Dir = ?copydir,
 
1800
    File = fname(Dir, "fun_mfa_vars.erl"),
 
1801
    MFile = fname(Dir, "fun_mfa_vars"),
 
1802
    Beam = fname(Dir, "fun_mfa_vars.beam"),
 
1803
    Test = <<"-module(fun_mfa_vars).
 
1804
 
 
1805
              -export([t/1, t1/1, t2/3]).
 
1806
 
 
1807
              t(Mod) ->
 
1808
                  F = fun Mod:bar/2,
 
1809
                  (F)(a, b).
 
1810
 
 
1811
              t1(Name) ->
 
1812
                  F = fun ?MODULE:Name/1,
 
1813
                  (F)(a).
 
1814
 
 
1815
              t2(Mod, Name, Arity) ->
 
1816
                  F = fun Mod:Name/Arity,
 
1817
                  (F)(a).
 
1818
 
 
1819
              t3(Arity) ->
 
1820
                  F = fun ?MODULE:t/Arity,
 
1821
                  (F)(1, 2, 3).
 
1822
 
 
1823
              t4(Mod, Name) ->
 
1824
                  F = fun Mod:Name/3,
 
1825
                  (F)(a, b, c).
 
1826
 
 
1827
              t5(Mod, Arity) ->
 
1828
                  F = fun Mod:t/Arity,
 
1829
                  (F)().
 
1830
             ">>,
 
1831
 
 
1832
    ok = file:write_file(File, Test),
 
1833
    A = fun_mfa_vars,
 
1834
    {ok, A} = compile:file(File, [report,debug_info,{outdir,Dir}]),
 
1835
    {ok, _} = xref:start(s),
 
1836
    {ok, A} = xref:add_module(s, MFile, {warnings,false}),
 
1837
    {ok, [{{{A,t,1},{'$M_EXPR','$F_EXPR',2}},[7]},
 
1838
          {{{A,t,1},{'$M_EXPR',bar,2}},[6]},
 
1839
          {{{A,t1,1},{'$M_EXPR','$F_EXPR',1}},[11]},
 
1840
          {{{A,t1,1},{A,'$F_EXPR',1}},[10]},
 
1841
          {{{A,t2,3},{'$M_EXPR','$F_EXPR',-1}},[14]},
 
1842
          {{{A,t2,3},{'$M_EXPR','$F_EXPR',1}},[15]},
 
1843
          {{{A,t3,1},{'$M_EXPR','$F_EXPR',3}},[19]},
 
1844
          {{{A,t3,1},{fun_mfa_vars,t,-1}},[18]},
 
1845
          {{{A,t4,2},{'$M_EXPR','$F_EXPR',3}},[22,23]},
 
1846
          {{{A,t5,2},{'$M_EXPR','$F_EXPR',0}},[27]},
 
1847
          {{{A,t5,2},{'$M_EXPR',t,-1}},[26]}]} =
 
1848
        xref:q(s, "(Lin) E"),
 
1849
 
 
1850
    ok = check_state(s),
 
1851
    xref:stop(s),
 
1852
 
 
1853
    ok = file:delete(File),
 
1854
    ok = file:delete(Beam),
 
1855
    ok.
 
1856
 
1750
1857
qlc(suite) -> [];
1751
1858
qlc(doc) -> ["OTP-5195: A bug fix when using qlc:q/1,2."];
1752
1859
qlc(Conf) when is_list(Conf) ->
1788
1895
    ok.
1789
1896
 
1790
1897
 
1791
 
analyses(suite) ->
1792
 
    [analyze, basic, md, q, variables, unused_locals].
1793
1898
 
1794
1899
analyze(suite) -> [];
1795
1900
analyze(doc) -> ["Simple analyses"];
2312
2417
    ?line ok = file:delete(Beam2),
2313
2418
    ok.
2314
2419
 
2315
 
misc(suite) ->
2316
 
    [format_error, otp_7423, otp_7831].
2317
2420
 
2318
2421
format_error(suite) -> [];
2319
2422
format_error(doc) -> ["Format error messages"];