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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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(rpc).
19
20
 
58
59
-export([init/1,handle_call/3,handle_cast/2,handle_info/2,
59
60
         terminate/2, code_change/3]).
60
61
 
61
 
%%------------------------------------------------------------------------
62
 
 
63
 
-type(node()    :: atom()).
64
 
-type(timeout() :: 'infinity' | non_neg_integer()).
 
62
%% Internals
 
63
-export([proxy_user_flush/0]).
65
64
 
66
65
%%------------------------------------------------------------------------
67
66
 
68
67
%% Remote execution and broadcasting facility
69
 
 
 
68
    
 
69
   
70
70
start() -> gen_server:start({local,?NAME},?MODULE,[],[]).
71
71
start_link() -> gen_server:start_link({local,?NAME},?MODULE,[],[]).
72
72
 
184
184
    group_leader(Gleader, self());
185
185
set_group_leader(user) -> 
186
186
    %% For example, hidden C nodes doesn't want any I/O.
 
187
    Gleader = case whereis(user) of
 
188
                  Pid when is_pid(Pid) -> Pid;
 
189
                  undefined -> proxy_user()
 
190
              end,
 
191
    group_leader(Gleader, self()).
 
192
 
 
193
 
 
194
%% The 'rex_proxy_user' process serve as group leader for early rpc's that
 
195
%% may do IO before the real group leader 'user' has been started (OTP-7903).
 
196
proxy_user() ->
 
197
    case whereis(rex_proxy_user) of
 
198
        Pid when is_pid(Pid) -> Pid;
 
199
        undefined ->
 
200
            Pid = spawn(fun()-> proxy_user_loop() end),
 
201
            try register(rex_proxy_user,Pid) of
 
202
                true -> Pid
 
203
            catch error:_ -> % spawn race, kill and try again
 
204
                exit(Pid,kill),
 
205
                proxy_user()
 
206
            end
 
207
    end.
 
208
 
 
209
proxy_user_loop() ->
 
210
    %% Wait for the real 'user' to start
 
211
    timer:sleep(200),
187
212
    case whereis(user) of
188
 
        Pid when is_pid(Pid) -> group_leader(Pid, self());
189
 
        _                    -> true
 
213
        Pid when is_pid(Pid) -> proxy_user_flush();
 
214
        undefined -> proxy_user_loop()
190
215
    end.
191
216
 
 
217
proxy_user_flush() ->
 
218
    %% Forward all received messages to 'user'
 
219
    receive Msg ->
 
220
            user ! Msg
 
221
    after 10*1000 ->
 
222
            %% Hibernate but live for ever, as it's not easy to know
 
223
            %% when no more messages will arrive.
 
224
            erlang:hibernate(?MODULE, proxy_user_flush, [])
 
225
    end,
 
226
    proxy_user_flush().
 
227
 
 
228
    
192
229
 
193
230
%% THE rpc client interface
194
231
 
497
534
parallel_eval(ArgL) ->
498
535
    Nodes = [node() | nodes()],
499
536
    Keys = map_nodes(ArgL,Nodes,Nodes),
500
 
    lists:map(fun yield/1,Keys).
 
537
    [yield(K) || K <- Keys].
501
538
 
502
539
map_nodes([],_,_) -> [];
503
540
map_nodes(ArgL,[],Original) ->