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

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_appup_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_appup_test).
 
24
 
 
25
-compile(export_all).
 
26
-compile({no_auto_import,[error/1]}).
 
27
 
 
28
-include("inets_test_lib.hrl").
 
29
 
 
30
 
 
31
                                                % t()     -> megaco_test_lib:t(?MODULE).
 
32
                                                % t(Case) -> megaco_test_lib:t({?MODULE, Case}).
 
33
 
 
34
 
 
35
%% Test server callbacks
 
36
init_per_testcase(_Case, Config) ->
 
37
    Config.
 
38
 
 
39
end_per_testcase(_Case, Config) ->
 
40
    Config.
 
41
 
 
42
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
43
 
 
44
all() -> 
 
45
    [appup].
 
46
 
 
47
groups() -> 
 
48
    [].
 
49
 
 
50
init_per_group(_GroupName, Config) ->
 
51
    Config.
 
52
 
 
53
end_per_group(_GroupName, Config) ->
 
54
    Config.
 
55
 
 
56
 
 
57
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
58
 
 
59
init_per_suite(suite) -> [];
 
60
init_per_suite(doc) -> [];
 
61
init_per_suite(Config) when is_list(Config) ->
 
62
    AppFile   = file_name(inets, ".app"),
 
63
    AppupFile = file_name(inets, ".appup"),
 
64
    [{app_file, AppFile}, {appup_file, AppupFile}|Config].
 
65
    
 
66
 
 
67
file_name(App, Ext) ->
 
68
    LibDir = code:lib_dir(App),
 
69
    filename:join([LibDir, "ebin", atom_to_list(App) ++ Ext]).
 
70
 
 
71
 
 
72
end_per_suite(suite) -> [];
 
73
end_per_suite(doc) -> [];
 
74
end_per_suite(Config) when is_list(Config) ->
 
75
    Config.
 
76
 
 
77
 
 
78
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
79
 
 
80
appup(suite) ->
 
81
    [];
 
82
appup(doc) ->
 
83
    "perform a simple check of the appup file";
 
84
appup(Config) when is_list(Config) ->
 
85
    AppupFile = key1search(appup_file, Config),
 
86
    AppFile   = key1search(app_file, Config),
 
87
    Modules   = modules(AppFile),
 
88
    check_appup(AppupFile, Modules).
 
89
 
 
90
modules(File) ->
 
91
    case file:consult(File) of
 
92
        {ok, [{application,inets,Info}]} ->
 
93
            case lists:keysearch(modules,1,Info) of
 
94
                {value, {modules, Modules}} ->
 
95
                    Modules;
 
96
                false ->
 
97
                    fail({bad_appinfo, Info})
 
98
            end;
 
99
        Error ->
 
100
            fail({bad_appfile, Error})
 
101
    end.
 
102
 
 
103
    
 
104
check_appup(AppupFile, Modules) ->
 
105
    case file:consult(AppupFile) of
 
106
        {ok, [{V, UpFrom, DownTo}]} ->
 
107
%           io:format("~p => "
 
108
%                     "~n  ~p"
 
109
%                     "~n  ~p"
 
110
%                     "~n", [V, UpFrom, DownTo]),
 
111
            check_appup(V, UpFrom, DownTo, Modules);
 
112
        Else ->
 
113
            fail({bad_appupfile, Else})
 
114
    end.
 
115
 
 
116
 
 
117
check_appup(V, UpFrom, DownTo, Modules) ->
 
118
    check_version(V),
 
119
    check_depends(up,   UpFrom, Modules),
 
120
    check_depends(down, DownTo, Modules),
 
121
    ok.
 
122
 
 
123
 
 
124
check_depends(_, [], _) ->
 
125
    ok;
 
126
check_depends(UpDown, [Dep|Deps], Modules) ->
 
127
    check_depend(UpDown, Dep, Modules),
 
128
    check_depends(UpDown, Deps, Modules).
 
129
 
 
130
 
 
131
check_depend(UpDown, {V, Instructions}, Modules) ->
 
132
    check_version(V),
 
133
    case check_instructions(UpDown, 
 
134
                            Instructions, Instructions, [], [], Modules) of
 
135
        {_Good, []} ->
 
136
            ok;
 
137
        {_, Bad} ->
 
138
            fail({bad_instructions, Bad, UpDown})
 
139
    end.
 
140
 
 
141
 
 
142
check_instructions(_, [], _, Good, Bad, _) ->
 
143
    {lists:reverse(Good), lists:reverse(Bad)};
 
144
check_instructions(UpDown, [Instr|Instrs], AllInstr, Good, Bad, Modules) ->
 
145
    case (catch check_instruction(UpDown, Instr, AllInstr, Modules)) of
 
146
        ok ->
 
147
            check_instructions(UpDown, Instrs, AllInstr, 
 
148
                               [Instr|Good], Bad, Modules);
 
149
        {error, Reason} ->
 
150
            check_instructions(UpDown, Instrs, AllInstr, Good, 
 
151
                               [{Instr, Reason}|Bad], Modules)
 
152
    end;
 
153
check_instructions(UpDown, Instructions, _, _, _, _) ->
 
154
    fail({bad_instructions, {UpDown, Instructions}}).
 
155
 
 
156
%% A new module is added
 
157
check_instruction(up, {add_module, Module}, _, Modules) 
 
158
  when is_atom(Module) ->
 
159
    check_module(Module, Modules);
 
160
 
 
161
%% An old module is re-added
 
162
check_instruction(down, {add_module, Module}, _, Modules) 
 
163
  when is_atom(Module) ->
 
164
    case (catch check_module(Module, Modules)) of
 
165
        {error, {unknown_module, Module, Modules}} ->
 
166
            ok;
 
167
        ok ->
 
168
            error({existing_readded_module, Module})
 
169
    end;
 
170
 
 
171
%% Removing a module on upgrade: 
 
172
%% - the module has been removed from the app-file.
 
173
%% - check that no module depends on this (removed) module
 
174
check_instruction(up, {remove, {Module, Pre, Post}}, _, Modules) 
 
175
  when is_atom(Module), is_atom(Pre), is_atom(Post) ->
 
176
    case (catch check_module(Module, Modules)) of
 
177
        {error, {unknown_module, Module, Modules}} ->
 
178
            check_purge(Pre),
 
179
            check_purge(Post);
 
180
        ok ->
 
181
            error({existing_removed_module, Module})
 
182
    end;
 
183
 
 
184
%% Removing a module on downgrade: the module exist
 
185
%% in the app-file.
 
186
check_instruction(down, {remove, {Module, Pre, Post}}, AllInstr, Modules) 
 
187
  when is_atom(Module), is_atom(Pre), is_atom(Post) ->
 
188
    case (catch check_module(Module, Modules)) of
 
189
        ok ->
 
190
            check_purge(Pre),
 
191
            check_purge(Post),
 
192
            check_no_remove_depends(Module, AllInstr);
 
193
        {error, {unknown_module, Module, Modules}} ->
 
194
            error({nonexisting_removed_module, Module})
 
195
    end;
 
196
 
 
197
check_instruction(up, {load_module, Module, Pre, Post, Depend}, _, Modules) 
 
198
  when is_atom(Module), is_atom(Pre), is_atom(Post), is_list(Depend) ->
 
199
    check_module(Module, Modules),
 
200
    check_module_depend(Module, Depend, Modules),
 
201
    check_purge(Pre),
 
202
    check_purge(Post);
 
203
 
 
204
check_instruction(down, {load_module, Module, Pre, Post, Depend}, _, Modules) 
 
205
  when is_atom(Module), is_atom(Pre), is_atom(Post), is_list(Depend) ->
 
206
    check_module(Module, Modules),
 
207
    % Can not be sure that the the dependent module exists in the new appfile 
 
208
    %%check_module_depend(Module, Depend, Modules),
 
209
    check_purge(Pre),
 
210
    check_purge(Post);
 
211
 
 
212
 
 
213
 
 
214
check_instruction(up, {delete_module, Module}, _, Modules) 
 
215
  when is_atom(Module) ->
 
216
    case (catch check_module(Module, Modules)) of
 
217
        {error, {unknown_module, Module, Modules}} ->
 
218
            ok;
 
219
        ok ->
 
220
            error({existing_module_deleted, Module})
 
221
    end;
 
222
 
 
223
check_instruction(down, {delete_module, Module}, _, Modules) 
 
224
  when is_atom(Module)  ->
 
225
    check_module(Module, Modules);
 
226
 
 
227
 
 
228
check_instruction(_, {apply, {Module, Function, Args}}, _, _) when is_atom(Module), is_atom(Function), is_list(Args) ->
 
229
    ok;
 
230
 
 
231
check_instruction(_, {update, Module, supervisor}, _, Modules) when is_atom(Module) ->
 
232
    check_module(Module, Modules);
 
233
 
 
234
check_instruction(_, {update, Module, {advanced, _}, DepMods}, _, Modules)  when is_atom(Module), is_list(DepMods) ->
 
235
    check_module(Module, Modules),
 
236
    check_module_depend(Module, DepMods, Modules);
 
237
 
 
238
check_instruction(_, {update, Module, Change, Pre, Post, Depend}, _, Modules) 
 
239
  when is_atom(Module), is_atom(Pre), is_atom(Post), is_list(Depend) ->
 
240
    check_module(Module, Modules),
 
241
    check_module_depend(Module, Depend, Modules),
 
242
    check_change(Change),
 
243
    check_purge(Pre),
 
244
    check_purge(Post);
 
245
 
 
246
check_instruction(_, {restart_application, inets}, _AllInstr, _Modules) ->
 
247
    ok;
 
248
 
 
249
check_instruction(_, {update, Module, {advanced, _}}, _, Modules) ->
 
250
    check_module(Module, Modules);
 
251
 
 
252
check_instruction(_, Instr, _AllInstr, _Modules) ->
 
253
    error({error, {unknown_instruction, Instr}}).
 
254
 
 
255
 
 
256
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
257
 
 
258
check_version(V) when is_list(V) ->
 
259
    ok;
 
260
check_version(V) ->
 
261
    error({bad_version, V}).
 
262
 
 
263
 
 
264
check_module(M, Modules) when is_atom(M) ->
 
265
    case lists:member(M,Modules) of
 
266
        true ->
 
267
            ok;
 
268
        false ->
 
269
            error({unknown_module, M, Modules})
 
270
    end;
 
271
check_module(M, _) ->
 
272
    error({bad_module, M}).
 
273
 
 
274
 
 
275
check_module_depend(M, [], _) when is_atom(M) ->
 
276
    ok;
 
277
check_module_depend(M, Deps, Modules) when is_atom(M), is_list(Deps) ->
 
278
    case [Dep || Dep <- Deps, lists:member(Dep, Modules) == false] of
 
279
        [] ->
 
280
            ok;
 
281
        Unknown ->
 
282
            error({unknown_depend_modules, Unknown})
 
283
    end;
 
284
check_module_depend(_M, D, _Modules) ->
 
285
    error({bad_depend, D}).
 
286
 
 
287
 
 
288
check_no_remove_depends(_Module, []) ->
 
289
    ok;
 
290
check_no_remove_depends(Module, [Instr|Instrs]) ->
 
291
    check_no_remove_depend(Module, Instr),
 
292
    check_no_remove_depends(Module, Instrs).
 
293
 
 
294
check_no_remove_depend(Module, {load_module, Mod, _Pre, _Post, Depend}) ->
 
295
    case lists:member(Module, Depend) of
 
296
        true ->
 
297
            error({removed_module_in_depend, load_module, Mod, Module});
 
298
        false ->
 
299
            ok
 
300
    end;
 
301
check_no_remove_depend(Module, {update, Mod, _Change, _Pre, _Post, Depend}) ->
 
302
    case lists:member(Module, Depend) of
 
303
        true ->
 
304
            error({removed_module_in_depend, update, Mod, Module});
 
305
        false ->
 
306
            ok
 
307
    end;
 
308
check_no_remove_depend(_, _) ->
 
309
    ok.
 
310
    
 
311
 
 
312
check_change(soft) ->
 
313
    ok;
 
314
check_change({advanced, _Something}) ->
 
315
    ok;
 
316
check_change(Change) ->
 
317
    error({bad_change, Change}).
 
318
 
 
319
 
 
320
check_purge(soft_purge) ->
 
321
    ok;
 
322
check_purge(brutal_purge) ->
 
323
    ok;
 
324
check_purge(Purge) ->
 
325
    error({bad_purge, Purge}).
 
326
 
 
327
 
 
328
 
 
329
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
330
 
 
331
error(Reason) ->
 
332
    throw({error, Reason}).
 
333
 
 
334
fail(Reason) ->
 
335
    exit({suite_failed, Reason}).
 
336
 
 
337
key1search(Key, L) ->
 
338
    case lists:keysearch(Key, 1, L) of
 
339
        undefined ->
 
340
            fail({not_found, Key, L});
 
341
        {value, {Key, Value}} ->
 
342
            Value
 
343
    end.