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

« back to all changes in this revision

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