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

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_app_test.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 2002-2010. 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
%%----------------------------------------------------------------------
 
21
%% Purpose: Verify the application specifics of the inets application
 
22
%%----------------------------------------------------------------------
 
23
-module(inets_app_test).
 
24
 
 
25
-compile(export_all).
 
26
 
 
27
-include("inets_test_lib.hrl").
 
28
 
 
29
 
 
30
% t()     -> megaco_test_lib:t(?MODULE).
 
31
% t(Case) -> megaco_test_lib:t({?MODULE, Case}).
 
32
 
 
33
 
 
34
%% Test server callbacks
 
35
init_per_testcase(undef_funcs, Config) ->
 
36
    NewConfig = lists:keydelete(watchdog, 1, Config),
 
37
    Dog = test_server:timetrap(inets_test_lib:minutes(10)),
 
38
    [{watchdog, Dog}| NewConfig];
 
39
init_per_testcase(_, Config) ->
 
40
    Config.
 
41
 
 
42
end_per_testcase(_Case, Config) ->
 
43
    Config.
 
44
 
 
45
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
46
 
 
47
all() -> 
 
48
    [fields, modules, exportall, app_depend,
 
49
     undef_funcs].
 
50
 
 
51
groups() -> 
 
52
    [].
 
53
 
 
54
init_per_group(_GroupName, Config) ->
 
55
    Config.
 
56
 
 
57
end_per_group(_GroupName, Config) ->
 
58
    Config.
 
59
 
 
60
 
 
61
 
 
62
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
63
 
 
64
init_per_suite(suite) -> [];
 
65
init_per_suite(doc) -> [];
 
66
init_per_suite(Config) when is_list(Config) ->
 
67
    case is_app(inets) of
 
68
        {ok, AppFile} ->
 
69
            io:format("AppFile: ~n~p~n", [AppFile]),
 
70
            inets:print_version_info(),
 
71
            [{app_file, AppFile}|Config];
 
72
        {error, Reason} ->
 
73
            fail(Reason)
 
74
    end.
 
75
 
 
76
is_app(App) ->
 
77
    LibDir = code:lib_dir(App),
 
78
    File = filename:join([LibDir, "ebin", atom_to_list(App) ++ ".app"]),
 
79
    case file:consult(File) of
 
80
        {ok, [{application, App, AppFile}]} ->
 
81
            {ok, AppFile};
 
82
        Error ->
 
83
            {error, {invalid_format, Error}}
 
84
    end.
 
85
 
 
86
 
 
87
end_per_suite(suite) -> [];
 
88
end_per_suite(doc) -> [];
 
89
end_per_suite(Config) when is_list(Config) ->
 
90
    Config.
 
91
 
 
92
 
 
93
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
94
 
 
95
fields(suite) ->
 
96
    [];
 
97
fields(doc) ->
 
98
    [];
 
99
fields(Config) when is_list(Config) ->
 
100
    AppFile = key1search(app_file, Config),
 
101
    Fields = [vsn, description, modules, registered, applications],
 
102
    case check_fields(Fields, AppFile, []) of
 
103
        [] ->
 
104
            ok;
 
105
        Missing ->
 
106
            fail({missing_fields, Missing})
 
107
    end.
 
108
 
 
109
check_fields([], _AppFile, Missing) ->
 
110
    Missing;
 
111
check_fields([Field|Fields], AppFile, Missing) ->
 
112
    check_fields(Fields, AppFile, check_field(Field, AppFile, Missing)).
 
113
 
 
114
check_field(Name, AppFile, Missing) ->
 
115
    io:format("checking field: ~p~n", [Name]),
 
116
    case lists:keymember(Name, 1, AppFile) of
 
117
        true ->
 
118
            Missing;
 
119
        false ->
 
120
            [Name|Missing]
 
121
    end.
 
122
 
 
123
 
 
124
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
125
 
 
126
modules(suite) ->
 
127
    [];
 
128
modules(doc) ->
 
129
    [];
 
130
modules(Config) when is_list(Config) ->
 
131
    AppFile  = key1search(app_file, Config),
 
132
    Mods     = key1search(modules, AppFile),
 
133
    EbinList = get_ebin_mods(inets),
 
134
    case missing_modules(Mods, EbinList, []) of
 
135
        [] ->
 
136
            ok;
 
137
        Missing ->
 
138
            throw({error, {missing_modules, Missing}})
 
139
    end,
 
140
    case extra_modules(Mods, EbinList, []) of
 
141
        [] ->
 
142
            ok;
 
143
        Extra ->
 
144
            throw({error, {extra_modules, Extra}})
 
145
    end,
 
146
    {ok, Mods}.
 
147
 
 
148
get_ebin_mods(App) ->
 
149
    LibDir  = code:lib_dir(App),
 
150
    EbinDir = filename:join([LibDir,"ebin"]),
 
151
    {ok, Files0} = file:list_dir(EbinDir),
 
152
    Files1 = [lists:reverse(File) || File <- Files0],
 
153
    [list_to_atom(lists:reverse(Name)) || [$m,$a,$e,$b,$.|Name] <- Files1].
 
154
 
 
155
 
 
156
missing_modules([], _Ebins, Missing) ->
 
157
    Missing;
 
158
missing_modules([Mod|Mods], Ebins, Missing) ->
 
159
    case lists:member(Mod, Ebins) of
 
160
        true ->
 
161
            missing_modules(Mods, Ebins, Missing);
 
162
        false ->
 
163
            io:format("missing module: ~p~n", [Mod]),
 
164
            missing_modules(Mods, Ebins, [Mod|Missing])
 
165
    end.
 
166
 
 
167
 
 
168
extra_modules(_Mods, [], Extra) ->
 
169
    Extra;
 
170
extra_modules(Mods, [Mod|Ebins], Extra) ->
 
171
    case lists:member(Mod, Mods) of
 
172
        true ->
 
173
            extra_modules(Mods, Ebins, Extra);
 
174
        false ->
 
175
            io:format("supefluous module: ~p~n", [Mod]),
 
176
            extra_modules(Mods, Ebins, [Mod|Extra])
 
177
    end.
 
178
 
 
179
 
 
180
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
181
 
 
182
 
 
183
exportall(suite) ->
 
184
    [];
 
185
exportall(doc) ->
 
186
    [];
 
187
exportall(Config) when is_list(Config) ->
 
188
    AppFile = key1search(app_file, Config),
 
189
    Mods    = key1search(modules, AppFile),
 
190
    check_export_all(Mods).
 
191
 
 
192
 
 
193
check_export_all([]) ->
 
194
    ok;
 
195
check_export_all([Mod|Mods]) ->
 
196
    case (catch apply(Mod, module_info, [compile])) of
 
197
        {'EXIT', {undef, _}} ->
 
198
            check_export_all(Mods);
 
199
        O ->
 
200
            case lists:keysearch(options, 1, O) of
 
201
                false ->
 
202
                    check_export_all(Mods);
 
203
                {value, {options, List}} ->
 
204
                    case lists:member(export_all, List) of
 
205
                        true ->
 
206
                            throw({error, {export_all, Mod}});
 
207
                        false ->
 
208
                            check_export_all(Mods)
 
209
                    end
 
210
            end
 
211
    end.
 
212
 
 
213
            
 
214
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
215
 
 
216
app_depend(suite) ->
 
217
    [];
 
218
app_depend(doc) ->
 
219
    [];
 
220
app_depend(Config) when is_list(Config) ->
 
221
    AppFile = key1search(app_file, Config),
 
222
    Apps    = key1search(applications, AppFile),
 
223
    check_apps(Apps).
 
224
 
 
225
 
 
226
check_apps([]) ->
 
227
    ok;
 
228
check_apps([App|Apps]) ->
 
229
    case is_app(App) of
 
230
        {ok, _} ->
 
231
            check_apps(Apps);
 
232
        Error ->
 
233
            throw({error, {missing_app, {App, Error}}})
 
234
    end.
 
235
 
 
236
 
 
237
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
238
 
 
239
undef_funcs(suite) ->
 
240
    [];
 
241
undef_funcs(doc) ->
 
242
    [];
 
243
undef_funcs(Config) when is_list(Config) ->
 
244
    App            = inets,
 
245
    AppFile        = key1search(app_file, Config),
 
246
    Mods           = key1search(modules, AppFile),
 
247
    Root           = code:root_dir(),
 
248
    LibDir         = code:lib_dir(App),
 
249
    EbinDir        = filename:join([LibDir,"ebin"]),
 
250
    XRefTestName   = undef_funcs_make_name(App, xref_test_name),
 
251
    {ok, XRef}     = xref:start(XRefTestName),
 
252
    ok             = xref:set_default(XRef, 
 
253
                                      [{verbose,false},{warnings,false}]),
 
254
    XRefName       = undef_funcs_make_name(App, xref_name),
 
255
    {ok, XRefName} = xref:add_release(XRef, Root, {name,XRefName}),
 
256
    {ok, App}      = xref:replace_application(XRef, App, EbinDir),
 
257
    {ok, Undefs}   = xref:analyze(XRef, undefined_function_calls),
 
258
    xref:stop(XRef),
 
259
    analyze_undefined_function_calls(Undefs, Mods, []).
 
260
 
 
261
analyze_undefined_function_calls([], _, []) ->
 
262
    ok;
 
263
analyze_undefined_function_calls([], _, AppUndefs) ->
 
264
    exit({suite_failed, {undefined_function_calls, AppUndefs}});
 
265
analyze_undefined_function_calls([{{Mod, _F, _A}, _C} = AppUndef|Undefs], 
 
266
                                 AppModules, AppUndefs) ->
 
267
    %% Check that this module is our's
 
268
    case lists:member(Mod,AppModules) of
 
269
        true ->
 
270
            {Calling,Called} = AppUndef,
 
271
            {Mod1,Func1,Ar1} = Calling,
 
272
            {Mod2,Func2,Ar2} = Called,
 
273
            io:format("undefined function call: "
 
274
                      "~n   ~w:~w/~w calls ~w:~w/~w~n", 
 
275
                      [Mod1,Func1,Ar1,Mod2,Func2,Ar2]),
 
276
            analyze_undefined_function_calls(Undefs, AppModules, 
 
277
                                             [AppUndef|AppUndefs]);
 
278
        false ->
 
279
            io:format("dropping ~p~n", [Mod]),
 
280
            analyze_undefined_function_calls(Undefs, AppModules, AppUndefs)
 
281
    end.
 
282
 
 
283
%% This function is used simply to avoid cut-and-paste errors later...
 
284
undef_funcs_make_name(App, PostFix) ->
 
285
    list_to_atom(atom_to_list(App) ++ "_" ++ atom_to_list(PostFix)).
 
286
 
 
287
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
288
 
 
289
 
 
290
fail(Reason) ->
 
291
    exit({suite_failed, Reason}).
 
292
 
 
293
key1search(Key, L) ->
 
294
    case lists:keysearch(Key, 1, L) of
 
295
        undefined ->
 
296
            fail({not_found, Key, L});
 
297
        {value, {Key, Value}} ->
 
298
            Value
 
299
    end.