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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/slave.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
54
54
pseudo(_) ->
55
55
    error_msg("No master node given to slave:pseudo/1~n",[]).
56
56
 
 
57
-spec pseudo(Master, ServerList) -> ok when
 
58
      Master :: node(),
 
59
      ServerList :: [atom()].
 
60
 
57
61
pseudo(_, []) -> ok;
58
62
pseudo(Master, [S|Tail]) ->
59
63
    start_pseudo(S, whereis(S), Master),
68
72
 
69
73
%% This relay can be used to relay all messages directed to a process.
70
74
 
 
75
-spec relay(Pid) -> no_return() when
 
76
      Pid :: pid().
 
77
 
71
78
relay({badrpc,Reason}) ->
72
79
    error_msg(" ** exiting relay server ~w :~w  **~n", [self(),Reason]),
73
80
    exit(Reason);
120
127
%%          {error, no_rsh} |
121
128
%%          {error, {already_running, Name@Host}}
122
129
 
 
130
-spec start(Host) -> {ok, Node} | {error, Reason} when
 
131
      Host :: atom(),
 
132
      Node :: node(),
 
133
      Reason :: timeout | no_rsh | {already_running, Node}.
 
134
 
123
135
start(Host) ->
124
136
    L = atom_to_list(node()),
125
137
    Name = upto($@, L),
126
 
    start(Host, Name).
 
138
    start(Host, Name, [], no_link).
 
139
 
 
140
-spec start(Host, Name) -> {ok, Node} | {error, Reason} when
 
141
      Host :: atom(),
 
142
      Name :: atom(),
 
143
      Node :: node(),
 
144
      Reason :: timeout | no_rsh | {already_running, Node}.
127
145
 
128
146
start(Host, Name) ->
129
147
    start(Host, Name, []).
130
148
 
 
149
-spec start(Host, Name, Args) -> {ok, Node} | {error, Reason} when
 
150
      Host :: atom(),
 
151
      Name :: atom(),
 
152
      Args :: string(),
 
153
      Node :: node(),
 
154
      Reason :: timeout | no_rsh | {already_running, Node}.
 
155
 
131
156
start(Host, Name, Args) ->
132
157
    start(Host, Name, Args, no_link).
133
158
 
 
159
-spec start_link(Host) -> {ok, Node} | {error, Reason} when
 
160
      Host :: atom(),
 
161
      Node :: node(),
 
162
      Reason :: timeout | no_rsh | {already_running, Node}.
 
163
 
134
164
start_link(Host) ->
135
165
    L = atom_to_list(node()),
136
166
    Name = upto($@, L),
137
 
    start_link(Host, Name).
 
167
    start(Host, Name, [], self()).
 
168
 
 
169
-spec start_link(Host, Name) -> {ok, Node} | {error, Reason} when
 
170
      Host :: atom(),
 
171
      Name :: atom(),
 
172
      Node :: node(),
 
173
      Reason :: timeout | no_rsh | {already_running, Node}.
138
174
 
139
175
start_link(Host, Name) ->
140
176
    start_link(Host, Name, []).
141
177
 
 
178
-spec start_link(Host, Name, Args) -> {ok, Node} | {error, Reason} when
 
179
      Host :: atom(),
 
180
      Name :: atom(),
 
181
      Args :: string(),
 
182
      Node :: node(),
 
183
      Reason :: timeout | no_rsh | {already_running, Node}.
 
184
 
142
185
start_link(Host, Name, Args) ->
143
186
    start(Host, Name, Args, self()).
144
187
 
163
206
 
164
207
%% Stops a running node.
165
208
 
 
209
-spec stop(Node) -> ok when
 
210
      Node :: node().
 
211
 
166
212
stop(Node) ->
167
213
%    io:format("stop(~p)~n", [Node]),
168
214
    rpc:call(Node, erlang, halt, []),