~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_appup_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

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