~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/kernel/src/application.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(application).
19
20
 
31
32
 
32
33
%%%-----------------------------------------------------------------
33
34
 
34
 
-type(node()    :: atom()).
35
 
-type(timeout() :: 'infinity' | non_neg_integer()).
36
 
 
37
 
-type(restart_type() :: 'permanent' | 'transient' | 'temporary').
38
 
-type(application_opt() :: {'description', string()}
 
35
-type restart_type() :: 'permanent' | 'transient' | 'temporary'.
 
36
-type application_opt() :: {'description', string()}
39
37
                         | {'vsn', string()}
40
38
                         | {'id', string()}
41
39
                         | {'modules', [atom() | {atom(), any()}]} 
46
44
                         | {'start_phases', [{atom(), any()}] | 'undefined'}
47
45
                         | {'maxT', timeout()}                % max timeout
48
46
                         | {'maxP', integer() | 'infinity'}   % max processes
49
 
                         | {'mod', {atom(), any()}}).
50
 
-type(application_spec() :: {'application', atom(), [application_opt()]}).
 
47
                         | {'mod', {atom(), any()}}.
 
48
-type application_spec() :: {'application', atom(), [application_opt()]}.
51
49
 
52
50
%%------------------------------------------------------------------
53
51
 
 
52
-spec behaviour_info(atom()) -> 'undefined' | [{atom(), byte()}].
 
53
 
54
54
behaviour_info(callbacks) ->
55
55
    [{start,2},{stop,1}];
56
56
behaviour_info(_Other) ->
61
61
%%% application_master.
62
62
%%%-----------------------------------------------------------------
63
63
 
64
 
-spec(load/1 :: (Application :: atom() | application_spec()) ->
65
 
             'ok' | {'error', any()}).
 
64
-spec load(Application :: atom() | application_spec()) ->
 
65
             'ok' | {'error', any()}.
66
66
 
67
67
load(Application) ->
68
68
    load(Application, []).
69
69
 
70
 
-spec(load/2 :: (Application :: atom() | application_spec(),
71
 
                 Distributed :: any()) -> 'ok' | {'error', any()}).
 
70
-spec load(Application :: atom() | application_spec(),
 
71
           Distributed :: any()) -> 'ok' | {'error', any()}.
72
72
 
73
73
load(Application, DistNodes) ->
74
74
    case application_controller:load_application(Application) of
85
85
            Else
86
86
    end.
87
87
 
88
 
-spec(unload/1 :: (Application :: atom()) -> 'ok' | {'error', any()}).
 
88
-spec unload(Application :: atom()) -> 'ok' | {'error', any()}.
89
89
 
90
90
unload(Application) ->
91
91
    application_controller:unload_application(Application).
92
92
 
93
 
-spec(start/1 :: (Application :: atom()) -> 'ok' | {'error', any()}).
 
93
-spec start(Application :: atom()) -> 'ok' | {'error', any()}.
94
94
 
95
95
start(Application) ->
96
96
    start(Application, temporary).
97
97
 
98
 
-spec(start/2 :: (Application :: atom() | application_spec(),
99
 
                  RestartType :: restart_type()) -> any()).
 
98
-spec start(Application :: atom() | application_spec(),
 
99
            RestartType :: restart_type()) -> any().
100
100
 
101
101
start(Application, RestartType) ->
102
102
    case load(Application) of
109
109
            Error
110
110
    end.
111
111
 
112
 
-spec(start_boot/1 :: (Application :: atom()) -> 'ok' | {'error', any()}).
 
112
-spec start_boot(Application :: atom()) -> 'ok' | {'error', any()}.
113
113
 
114
114
start_boot(Application) ->
115
115
    start_boot(Application, temporary).
116
116
 
117
 
-spec(start_boot/2 :: (Application :: atom(), RestartType :: restart_type()) ->
118
 
             'ok' | {'error', any()}).
 
117
-spec start_boot(Application :: atom(), RestartType :: restart_type()) ->
 
118
             'ok' | {'error', any()}.
119
119
 
120
120
start_boot(Application, RestartType) ->
121
121
    application_controller:start_boot_application(Application, RestartType).
122
122
 
123
 
-spec(takeover/2 :: (Application :: atom(), RestartType :: restart_type()) ->
124
 
             any()).
 
123
-spec takeover(Application :: atom(), RestartType :: restart_type()) -> any().
125
124
 
126
125
takeover(Application, RestartType) ->
127
126
    dist_ac:takeover_application(Application, RestartType).
128
127
 
129
 
-spec(permit/2 :: (Application :: atom(), Bool :: bool()) ->
130
 
             'ok' | {'error', any()}).
 
128
-spec permit(Application :: atom(), Bool :: bool()) -> 'ok' | {'error', any()}.
131
129
 
132
130
permit(Application, Bool) ->
133
131
    case Bool of
144
142
            LocalResult
145
143
    end.
146
144
 
147
 
-spec(stop/1 :: (Application :: atom()) -> 'ok' | {'error', any()}).
 
145
-spec stop(Application :: atom()) -> 'ok' | {'error', any()}.
148
146
 
149
147
stop(Application) ->
150
148
    application_controller:stop_application(Application).
151
149
 
152
 
-spec(which_applications/0 :: () -> [{atom(), string(), string()}]).
 
150
-spec which_applications() -> [{atom(), string(), string()}].
153
151
 
154
152
which_applications() ->
155
153
    application_controller:which_applications().
156
154
 
157
 
-spec(which_applications/1 :: (timeout()) -> [{atom(), string(), string()}]).
 
155
-spec which_applications(timeout()) -> [{atom(), string(), string()}].
158
156
 
159
157
which_applications(infinity) ->
160
158
    application_controller:which_applications(infinity);
161
159
which_applications(Timeout) when is_integer(Timeout), Timeout>=0 ->
162
160
    application_controller:which_applications(Timeout).
163
161
 
164
 
-spec(loaded_applications/0 :: () -> [{atom(), string(), string()}]).
 
162
-spec loaded_applications() -> [{atom(), string(), string()}].
165
163
 
166
164
loaded_applications() -> 
167
165
    application_controller:loaded_applications().
168
166
 
169
 
-spec(info/0 :: () -> any()).
 
167
-spec info() -> any().
170
168
 
171
169
info() -> 
172
170
    application_controller:info().
173
171
 
174
 
-spec(set_env/3 :: (Application :: atom(), Key :: atom(),
175
 
                    Value :: any()) -> 'ok').
 
172
-spec set_env(Application :: atom(), Key :: atom(), Value :: any()) -> 'ok'.
176
173
 
177
174
set_env(Application, Key, Val) -> 
178
175
    application_controller:set_env(Application, Key, Val).
179
176
 
180
 
-spec(set_env/4 :: (Application :: atom(), Key :: atom(),
181
 
                    Value :: any(), Timeout :: timeout()) -> 'ok').
 
177
-spec set_env(Application :: atom(), Key :: atom(),
 
178
              Value :: any(), Timeout :: timeout()) -> 'ok'.
182
179
 
183
180
set_env(Application, Key, Val, infinity) ->
184
181
    application_controller:set_env(Application, Key, Val, infinity);
185
182
set_env(Application, Key, Val, Timeout) when is_integer(Timeout), Timeout>=0 ->
186
183
    application_controller:set_env(Application, Key, Val, Timeout).
187
184
 
188
 
-spec(unset_env/2 :: (Application :: atom(), Key :: atom()) -> 'ok').
 
185
-spec unset_env(atom(), atom()) -> 'ok'.
189
186
 
190
187
unset_env(Application, Key) -> 
191
188
    application_controller:unset_env(Application, Key).
192
189
 
193
 
-spec(unset_env/3 :: (Application :: atom(), Key :: atom(),
194
 
                      Timeout :: timeout()) -> 'ok').
 
190
-spec unset_env(atom(), atom(), timeout()) -> 'ok'.
195
191
 
196
192
unset_env(Application, Key, infinity) ->
197
193
    application_controller:unset_env(Application, Key, infinity);
198
194
unset_env(Application, Key, Timeout) when is_integer(Timeout), Timeout>=0 ->
199
195
    application_controller:unset_env(Application, Key, Timeout).
200
196
 
201
 
-spec(get_env/1 :: (Key :: atom()) -> 'undefined' | {'ok', any()}).
 
197
-spec get_env(atom()) -> 'undefined' | {'ok', any()}.
202
198
 
203
199
get_env(Key) -> 
204
200
    application_controller:get_pid_env(group_leader(), Key).
205
201
 
206
 
-spec(get_env/2 :: (Application :: atom(), Key :: atom()) ->
207
 
             'undefined' | {'ok', any()}).
 
202
-spec get_env(atom(), atom()) -> 'undefined' | {'ok', any()}.
208
203
 
209
204
get_env(Application, Key) -> 
210
205
    application_controller:get_env(Application, Key).
211
206
 
212
 
-spec(get_all_env/0 :: () -> [] | [{atom(), any()}]).
 
207
-spec get_all_env() -> [] | [{atom(), any()}].
213
208
 
214
209
get_all_env() -> 
215
210
    application_controller:get_pid_all_env(group_leader()).
216
211
 
217
 
-spec(get_all_env/1 :: (Application :: atom()) -> [] | [{atom(),any()}]).
 
212
-spec get_all_env(atom()) -> [] | [{atom(),any()}].
218
213
 
219
214
get_all_env(Application) -> 
220
215
    application_controller:get_all_env(Application).
221
216
 
222
 
-spec(get_key/1 :: (Key :: atom()) -> 'undefined' | {'ok', any()}).
 
217
-spec get_key(atom()) -> 'undefined' | {'ok', any()}.
223
218
 
224
219
get_key(Key) -> 
225
220
    application_controller:get_pid_key(group_leader(), Key).
226
221
 
227
 
-spec(get_key/2 :: (Application :: atom(), Key :: atom()) ->
228
 
             'undefined' | {'ok', any()}).
 
222
-spec get_key(atom(), atom()) -> 'undefined' | {'ok', any()}.
229
223
 
230
224
get_key(Application, Key) -> 
231
225
    application_controller:get_key(Application, Key).
232
226
 
233
 
-spec(get_all_key/0 :: () -> 'undefined' | [] | {'ok', [{atom(),any()},...]}).
 
227
-spec get_all_key() -> 'undefined' | [] | {'ok', [{atom(),any()},...]}.
234
228
 
235
229
get_all_key() ->
236
230
    application_controller:get_pid_all_key(group_leader()).
237
231
 
238
 
-spec(get_all_key/1 :: (Application :: atom()) -> 
239
 
             'undefined' | [] | {'ok', [{atom(),any()}]}).
 
232
-spec get_all_key(atom()) -> 'undefined' | [] | {'ok', [{atom(),any()}]}.
240
233
 
241
234
get_all_key(Application) -> 
242
235
    application_controller:get_all_key(Application).
243
236
 
244
 
-spec(get_application/0 :: () -> 'undefined' | {'ok', atom()}).
 
237
-spec get_application() -> 'undefined' | {'ok', atom()}.
245
238
 
246
239
get_application() -> 
247
240
    application_controller:get_application(group_leader()).
248
241
 
249
 
-spec(get_application/1 :: (Pid :: pid()) -> 'undefined' | {'ok', atom()}
250
 
                         ; (Module :: atom()) -> 'undefined' | {'ok', atom()}).
 
242
-spec get_application(Pid :: pid()) -> 'undefined' | {'ok', atom()}
 
243
                   ; (Module :: atom()) -> 'undefined' | {'ok', atom()}.
251
244
 
252
245
get_application(Pid) when is_pid(Pid) ->
253
246
    case process_info(Pid, group_leader) of
259
252
get_application(Module) when is_atom(Module) ->
260
253
    application_controller:get_application_module(Module).
261
254
 
262
 
-spec(start_type/0 :: () -> 'undefined' | 'local' | 'normal'
263
 
                          | {'takeover', node()} | {'failover', node()}).
 
255
-spec start_type() -> 'undefined' | 'local' | 'normal'
 
256
                    | {'takeover', node()} | {'failover', node()}.
264
257
 
265
258
start_type() ->
266
259
    application_controller:start_type(group_leader()).