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

« back to all changes in this revision

Viewing changes to lib/sasl/src/systools_rc.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
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
34
34
%% {add_module, Mod, [Mod]}
35
35
%% {remove_module, Mod, PrePurge, PostPurge, [Mod]}
36
36
%% {restart_application, Appl}
37
 
%% {add_application, Appl}
 
37
%% {add_application, Appl, Type}
38
38
%% {remove_application, Appl}
39
39
%%
40
40
%% Low-level
109
109
             {delete_module, Mod} ->
110
110
                 [{remove, {Mod, brutal_purge, brutal_purge}},
111
111
                  {purge, [Mod]}];
 
112
             {add_application, Application} ->
 
113
                 {add_application, Application, permanent};
112
114
             _ ->
113
115
                 I
114
116
         end,
317
319
translate_application_instrs(Script, Appls, PreAppls) ->
318
320
    %% io:format("Appls ~n~p~n",[Appls]),
319
321
    L = lists:map(
320
 
          fun({add_application, Appl}) ->
 
322
          fun({add_application, Appl, Type}) ->
321
323
                  case lists:keysearch(Appl, #application.name, Appls) of
322
324
                      {value, Application} ->
323
325
                          Mods =
324
326
                              remove_vsn(Application#application.modules),
 
327
                          ApplyL = case Type of
 
328
                              none -> [];
 
329
                              load -> [{apply, {application, load, [Appl]}}];
 
330
                              _ -> [{apply, {application, start, [Appl, Type]}}]
 
331
                          end,
325
332
                          [{add_module, M, []} || M <- Mods] ++
326
 
                              [{apply, {application, start,
327
 
                                        [Appl, permanent]}}];
 
333
                              ApplyL;
328
334
                      false ->
329
335
                          throw({error, {no_such_application, Appl}})
330
336
                  end;
750
756
    lists:foreach(fun(M) -> check_mod(M) end, Mods);
751
757
check_op({remove_application, Appl}) ->
752
758
    check_appl(Appl);
753
 
check_op({add_application, Appl}) ->
754
 
    check_appl(Appl);
 
759
check_op({add_application, Appl, Type}) ->
 
760
    check_appl(Appl),
 
761
    check_start_type(Type);
755
762
check_op({restart_application, Appl}) ->
756
763
    check_appl(Appl);
757
764
check_op(restart) -> ok;
839
846
check_appl(Appl) when is_atom(Appl) -> ok;
840
847
check_appl(Appl) -> throw({error, {bad_application, Appl}}).
841
848
 
 
849
check_start_type(none) -> ok;
 
850
check_start_type(load) -> ok;
 
851
check_start_type(temporary) -> ok;
 
852
check_start_type(transient) -> ok;
 
853
check_start_type(permanent) -> ok;
 
854
check_start_type(T) -> throw({error, {bad_start_type, T}}).
 
855
 
842
856
check_func(Func) when is_atom(Func) -> ok;
843
857
check_func(Func) -> throw({error, {bad_func, Func}}).
844
858