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

« back to all changes in this revision

Viewing changes to lib/sasl/src/systools_relup.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 1996-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-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
112
112
-export([mk_relup/3, mk_relup/4, format_error/1, format_warning/1]).
113
113
-include("systools.hrl").
114
114
 
 
115
-define(R15_SASL_VSN,"2.2").
 
116
 
 
117
%% For test purposes only - used by kernel, stdlib and sasl tests
 
118
-export([appup_search_for_version/2]).
 
119
 
115
120
%%-----------------------------------------------------------------
116
121
%% mk_relup(TopRelFile, BaseUpRelDcs, BaseDnRelDcs)
117
122
%% mk_relup(TopRelFile, BaseUpRelDcs, BaseDnRelDcs, Opts) -> Ret
122
127
%% rel_filename() = description() = string()
123
128
%% Opts = [opt()]
124
129
%% opt() = {path, [path()]} | silent | noexec | restart_emulator
125
 
%%       | {outdir, string()}
 
130
%%       | {outdir, string()} | warnings_as_errors
126
131
%% path() = [string()]
127
132
%% Ret = ok | error | {ok, Relup, Module, Warnings} | {error, Module, Error}
128
133
%%
139
144
%% 
140
145
%% The option `path' sets search path, `silent' suppresses printing of
141
146
%% error messages to the console, `noexec' inhibits the creation of
142
 
%% the output "relup" file, and restart_emulator ensures that the new
143
 
%% emulator is restarted (as the final step).
 
147
%% the output "relup" file, restart_emulator ensures that the new
 
148
%% emulator is restarted (as the final step), and `warnings_as_errors'
 
149
%% treats warnings as errors.
144
150
%% ----------------------------------------------------------------
145
151
mk_relup(TopRelFile, BaseUpRelDcs, BaseDnRelDcs) ->
146
152
    mk_relup(TopRelFile, BaseUpRelDcs, BaseDnRelDcs, []).
153
159
                {false, false} ->
154
160
                    case R of
155
161
                        {ok, _Res, _Mod, Ws} -> 
156
 
                            print_warnings(Ws),
157
 
                            ok;
 
162
                            print_warnings(Ws, Opts),
 
163
                            case systools_lib:werror(Opts, Ws) of
 
164
                                true ->
 
165
                                    error;
 
166
                                false ->
 
167
                                    ok
 
168
                            end;
158
169
                        Other -> 
159
170
                            print_error(Other),
160
171
                            error
161
172
                    end;
162
 
                _ -> 
163
 
                    R
 
173
                _ ->
 
174
                    case R of
 
175
                        {ok, _Res, _Mod, Ws} ->
 
176
                            case systools_lib:werror(Opts, Ws) of
 
177
                                true ->
 
178
                                    error;
 
179
                                false ->
 
180
                                    R
 
181
                            end;
 
182
                        R ->
 
183
                            R
 
184
                    end
164
185
            end;
165
186
        BadArg ->
166
187
            erlang:error({badarg, BadArg})
179
200
    [].
180
201
 
181
202
do_mk_relup(TopRelFile, BaseUpRelDcs, BaseDnRelDcs, Path, Opts) ->
182
 
    ModTest = false,
183
 
    case systools_make:get_release(to_list(TopRelFile), Path, ModTest) of
 
203
    case systools_make:get_release(to_list(TopRelFile), Path) of
184
204
        %%
185
205
        %% TopRel = #release
186
206
        %% NameVsnApps = [{{Name, Vsn}, #application}]
187
207
        {ok, TopRel, NameVsnApps, Ws0} ->
188
 
            %%
 
208
            case lists:member({warning,missing_sasl},Ws0) of
 
209
                true ->
 
210
                    throw({error,?MODULE,{missing_sasl,TopRel}});
 
211
                false ->
 
212
                    ok
 
213
            end,
 
214
 
189
215
            %% TopApps = [#application]
190
216
            TopApps = lists:map(fun({_, App}) -> App end, NameVsnApps),
191
217
 
196
222
            {Dn, Ws2} = foreach_baserel_dn(TopRel, TopApps, BaseDnRelDcs, 
197
223
                                          Path, Opts, Ws1),
198
224
            Relup = {TopRel#release.vsn, Up, Dn},
199
 
            write_relup_file(Relup, Opts),
 
225
            case systools_lib:werror(Opts, Ws2) of
 
226
                true ->
 
227
                    ok;
 
228
                false ->
 
229
                    write_relup_file(Relup, Opts)
 
230
            end,
200
231
            {ok, Relup, ?MODULE, Ws2};
201
232
        Other -> 
202
233
            throw(Other)
227
258
               Ws, Acc) ->
228
259
    BaseRelFile = extract_filename(BaseRelDc),
229
260
 
230
 
    {ok, BaseRel} = systools_make:read_release(BaseRelFile, Path),
 
261
    {BaseRel, {BaseNameVsns, BaseApps}, Ws0} =
 
262
        case systools_make:get_release(BaseRelFile, Path) of
 
263
            {ok, BR, NameVsnApps, Warns} ->
 
264
                case lists:member({warning,missing_sasl},Warns) of
 
265
                    true ->
 
266
                        throw({error,?MODULE,{missing_sasl,BR}});
 
267
                    false ->
 
268
                        %% NameVsnApps = [{{Name,Vsn},#application}]
 
269
                        %% Gives two lists - [{Name,Vsn}] and [#application]
 
270
                        {BR,lists:unzip(NameVsnApps),Warns}
 
271
                end;
 
272
            Other1 ->
 
273
                throw(Other1)
 
274
        end,
 
275
 
231
276
 
232
277
    %%
233
278
    %% BaseRel = #release
237
282
    %% application, one for each added applications, and one for
238
283
    %% each removed applications.
239
284
    %%
240
 
    {RUs1, Ws1} = collect_appup_scripts(up, TopApps, BaseRel, Ws, []),
 
285
    {RUs1, Ws1} = collect_appup_scripts(up, TopApps, BaseRel, Ws0++Ws, []),
241
286
 
242
287
    {RUs2, Ws2} = create_add_app_scripts(BaseRel, TopRel, RUs1, Ws1),
243
288
 
244
289
    {RUs3, Ws3} = create_remove_app_scripts(BaseRel, TopRel, RUs2, Ws2),
245
290
 
246
 
    {RUs4, Ws4} = 
247
 
        check_for_emulator_restart(TopRel, BaseRel, RUs3, Ws3, Opts),
248
 
 
249
 
    ModTest = false,
250
 
    BaseApps =
251
 
        case systools_make:get_release(BaseRelFile, Path, ModTest) of
252
 
            {ok, _, NameVsnApps, _Warns} ->
253
 
                lists:map(fun({_,App}) -> App end, NameVsnApps);
254
 
            Other1 ->
255
 
                throw(Other1)
256
 
        end,
 
291
    {RUs4, Ws4} = check_for_emulator_restart(TopRel, BaseRel, RUs3, Ws3, Opts),
257
292
 
258
293
    case systools_rc:translate_scripts(up, RUs4, TopApps, BaseApps) of
259
 
        {ok, RUs} ->
 
294
        {ok, RUs5} ->
 
295
 
 
296
            {RUs, Ws5} = fix_r15_sasl_upgrade(RUs5,Ws4,BaseNameVsns),
 
297
 
260
298
            VDR = {BaseRel#release.vsn,
261
299
                   extract_description(BaseRelDc), RUs},
262
300
            foreach_baserel_up(TopRel, TopApps, BaseRelDcs, Path, 
263
 
                               Opts, Ws4, [VDR| Acc]);
 
301
                               Opts, Ws5, [VDR| Acc]);
264
302
        XXX ->
265
303
            throw(XXX)
266
304
    end;
275
313
               Ws, Acc) ->
276
314
    BaseRelFile = extract_filename(BaseRelDc),
277
315
 
278
 
    {ok, BaseRel} = systools_make:read_release(BaseRelFile, Path),
279
 
 
280
 
    %% BaseRel = #release
281
 
 
282
 
    %% RUs = (release upgrade scripts)
283
 
    %%
284
 
    {RUs1, Ws1} = collect_appup_scripts(dn, TopApps, BaseRel, Ws, []),
285
 
 
286
 
    ModTest = false,
287
 
    {BaseApps, Ws2} =
288
 
        case systools_make:get_release(BaseRelFile, Path, ModTest) of
 
316
    {BaseRel, BaseApps, Ws0} =
 
317
        case systools_make:get_release(BaseRelFile, Path) of
289
318
            %%
290
319
            %% NameVsnApps = [{{Name, Vsn}, #application}]
291
 
            {ok, _, NameVsnApps, Warns} ->
292
 
                %%
293
 
                %% NApps = [#application]
294
 
                NApps = lists:map(fun({_,App}) -> App end, NameVsnApps),
295
 
                {NApps, Warns ++ Ws1};
 
320
            {ok, BR, NameVsnApps, Warns} ->
 
321
                case lists:member({warning,missing_sasl},Warns) of
 
322
                    true ->
 
323
                        throw({error,?MODULE,{missing_sasl,BR}});
 
324
                    false ->
 
325
                        %% NApps = [#application]
 
326
                        NApps = lists:map(fun({_,App}) -> App end, NameVsnApps),
 
327
                        {BR, NApps, Warns}
 
328
                end;
296
329
            Other ->
297
330
                throw(Other)
298
331
        end,
299
332
 
300
 
    RUs2 = RUs1,
301
 
 
302
 
    {RUs3, Ws3} = create_add_app_scripts(TopRel, BaseRel, RUs2, Ws2),
303
 
 
304
 
    {RUs4, Ws4} = create_remove_app_scripts(TopRel, BaseRel, RUs3, Ws3),
305
 
 
306
 
    {RUs5, Ws5} = check_for_emulator_restart(TopRel, BaseRel,
307
 
                                             RUs4, Ws4, Opts),
308
 
 
309
 
    case systools_rc:translate_scripts(dn, RUs5, BaseApps, TopApps) of
 
333
    %% BaseRel = #release
 
334
 
 
335
    %% RUs = (release upgrade scripts)
 
336
    %%
 
337
    {RUs1, Ws1} = collect_appup_scripts(dn, TopApps, BaseRel, Ws0++Ws, []),
 
338
 
 
339
    {RUs2, Ws2} = create_add_app_scripts(TopRel, BaseRel, RUs1, Ws1),
 
340
 
 
341
    {RUs3, Ws3} = create_remove_app_scripts(TopRel, BaseRel, RUs2, Ws2),
 
342
 
 
343
    {RUs4, Ws4} = check_for_emulator_restart(TopRel, BaseRel, RUs3, Ws3, Opts),
 
344
 
 
345
    case systools_rc:translate_scripts(dn, RUs4, BaseApps, TopApps) of
310
346
        {ok, RUs} ->
311
347
            VDR = {BaseRel#release.vsn,
312
348
                   extract_description(BaseRelDc), RUs},
313
349
            foreach_baserel_dn(TopRel, TopApps, BaseRelDcs, Path, 
314
 
                               Opts, Ws5, [VDR| Acc]);
 
350
                               Opts, Ws4, [VDR| Acc]);
315
351
        XXX -> 
316
352
            throw(XXX)
317
353
    end;
325
361
%%
326
362
check_for_emulator_restart(#release{erts_vsn = Vsn1, name = N1}, 
327
363
                           #release{erts_vsn = Vsn2, name = N2}, RUs, Ws, 
328
 
                           _Opts) when Vsn1 /= Vsn2 ->
329
 
    {RUs++[[restart_new_emulator]], [{erts_vsn_changed, {N1, N2}} | Ws]};
 
364
                           Opts) when Vsn1 /= Vsn2 ->
 
365
    %% Automatically insert a restart_new_emulator instruction when
 
366
    %% erts version is changed. Also allow extra restart at the end of
 
367
    %% the upgrade if restart_emulator option is given.
 
368
    NewRUs = [[restart_new_emulator]|RUs],
 
369
    NewWs = [{erts_vsn_changed, {{N1,Vsn1}, {N2,Vsn2}}} | Ws],
 
370
    check_for_restart_emulator_opt(NewRUs, NewWs, Opts);
330
371
check_for_emulator_restart(_, _, RUs, Ws, Opts) ->
 
372
    check_for_restart_emulator_opt(RUs, Ws, Opts).
 
373
 
 
374
check_for_restart_emulator_opt(RUs, Ws, Opts) ->
331
375
    case get_opt(restart_emulator, Opts) of
332
 
        true -> {RUs++[[restart_new_emulator]], Ws};
 
376
        true -> {RUs++[[restart_emulator]], Ws};
333
377
        _ -> {RUs, Ws}
334
378
    end.
335
379
 
 
380
 
 
381
%% Special handling of the upgrade from pre R15 to post R15. In R15,
 
382
%% upgrade of the emulator was improved by moving the restart of the
 
383
%% emulator before the rest of the upgrade instructions. However, it
 
384
%% can only work if the release_handler is already upgraded to a post
 
385
%% R15 version. If not, the upgrade instructions must be backwards
 
386
%% compatible - i.e. restart_new_emulator will be the last
 
387
%% instruction, executed after all code loading, code_change etc.
 
388
fix_r15_sasl_upgrade([restart_new_emulator | RestRUs]=RUs, Ws, BaseApps) ->
 
389
    case lists:keyfind(sasl,1,BaseApps) of
 
390
        {sasl,Vsn} when Vsn < ?R15_SASL_VSN ->
 
391
            {lists:delete(restart_emulator,RestRUs) ++ [restart_new_emulator],
 
392
             [pre_R15_emulator_upgrade|Ws]};
 
393
        _ ->
 
394
            {RUs,Ws}
 
395
    end;
 
396
fix_r15_sasl_upgrade(RUs, Ws, _BaseApps) ->
 
397
    {RUs,Ws}.
 
398
 
 
399
 
336
400
%% collect_appup_scripts(Mode, TopApps, BaseRel, Ws, RUs) -> {NRUs, NWs}
337
401
%% Mode = up | dn
338
402
%% TopApps = [#application]
370
434
%% ToApps = [#application]
371
435
%%
372
436
create_add_app_scripts(FromRel, ToRel, RU0s, W0s) -> 
373
 
    AddedNs = [N || {N, _V, _T} <- ToRel#release.applications,
 
437
    AddedNs = [{N, T} || {N, _V, T} <- ToRel#release.applications,
374
438
                    not lists:keymember(N, 1, FromRel#release.applications)],
375
439
    %% io:format("Added apps: ~p~n", [AddedNs]),
376
 
    RUs = [[{add_application, N}] || N <- AddedNs],
 
440
    RUs = [[{add_application, N, T}] || {N, T} <- AddedNs],
377
441
    {RUs ++ RU0s, W0s}.
378
442
 
379
443
 
422
486
                  %% XXX Why is this a warning only?
423
487
                  [{bad_vsn, {TopVsn, TopApp#application.vsn}}| Ws]
424
488
          end,
425
 
    case lists:keysearch(BaseVsn, 1, VsnRUs) of
426
 
        {value, {_, RU}} ->
 
489
    case appup_search_for_version(BaseVsn, VsnRUs) of
 
490
        {ok, RU} ->
427
491
            {RUs ++ [RU], Ws1};
428
 
        _ ->
 
492
        error ->
429
493
            throw({error, ?MODULE, {no_relup, FName, TopApp, BaseVsn}})
430
494
    end.
431
495
 
 
496
appup_search_for_version(BaseVsn, VsnRUs) ->
 
497
    appup_search_for_version(BaseVsn, length(BaseVsn), VsnRUs).
 
498
 
 
499
appup_search_for_version(BaseVsn,_,[{BaseVsn,RU}|_]) ->
 
500
    {ok,RU};
 
501
appup_search_for_version(BaseVsn,Size,[{Vsn,RU}|VsnRUs]) when is_binary(Vsn) ->
 
502
    case re:run(BaseVsn,Vsn,[unicode,{capture,first,index}]) of
 
503
        {match,[{0,Size}]} ->
 
504
            {ok, RU};
 
505
        _ ->
 
506
            appup_search_for_version(BaseVsn,Size,VsnRUs)
 
507
    end;
 
508
appup_search_for_version(BaseVsn,Size,[_|VsnRUs]) ->
 
509
    appup_search_for_version(BaseVsn,Size,VsnRUs);
 
510
appup_search_for_version(_,_,[]) ->
 
511
    error.
 
512
 
 
513
 
 
514
 
432
515
 
433
516
%% Primitives for the "lists of release names" that we upgrade from
434
517
%% and to.
525
608
                  "in file ~p~n",
526
609
                  [App#application.name, App#application.vsn, 
527
610
                   App#application.name, Vsn, File]);
528
 
 
 
611
format_error({missing_sasl,Release}) ->
 
612
    io_lib:format("No sasl application in release ~p, ~p. Can not be upgraded.",
 
613
                  [Release#release.name, Release#release.vsn]);
529
614
format_error(Error) ->
530
615
    io:format("~p~n", [Error]).
531
616
 
532
617
 
533
 
print_warnings(Ws) when is_list(Ws) ->
534
 
    lists:foreach(fun(W) -> print_warning(W) end, Ws);
535
 
print_warnings(W) ->
536
 
    print_warning(W).
 
618
print_warnings(Ws, Opts) when is_list(Ws) ->
 
619
    lists:foreach(fun(W) -> print_warning(W, Opts) end, Ws);
 
620
print_warnings(W, Opts) ->
 
621
    print_warning(W, Opts).
537
622
 
538
 
print_warning(W) ->
539
 
    S = format_warning(W),
 
623
print_warning(W, Opts) ->
 
624
    Prefix = case lists:member(warnings_as_errors, Opts) of
 
625
                 true ->
 
626
                     "";
 
627
                 false ->
 
628
                     "*WARNING* "
 
629
             end,
 
630
    S = format_warning(Prefix, W),
540
631
    io:format("~s", [S]).
541
632
 
542
 
format_warning({erts_vsn_changed, {Rel1, Rel2}}) ->
543
 
    io_lib:format("*WARNING* The ERTS version changed between ~p and ~p~n",
544
 
                  [Rel1, Rel2]);
545
 
format_warning(What) ->
546
 
    io_lib:format("*WARNING* ~p~n",[What]).
 
633
format_warning(W) ->
 
634
    format_warning("*WARNING* ", W).
 
635
 
 
636
format_warning(Prefix, {erts_vsn_changed, {Rel1, Rel2}}) ->
 
637
    io_lib:format("~sThe ERTS version changed between ~p and ~p~n",
 
638
                  [Prefix, Rel1, Rel2]);
 
639
format_warning(Prefix, What) ->
 
640
    io_lib:format("~s~p~n",[Prefix, What]).
547
641
 
548
642
 
549
643
get_reason({error, {open, _, _}}) -> open;