~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
98
98
            {error, Hostname}
99
99
    end.
100
100
 
101
 
%% a common situation in "life" is to have a configuration file with a list
 
101
%% A common situation in "life" is to have a configuration file with a list
102
102
%% of nodes, and then at startup, all nodes in the list are ping'ed
103
103
%% this can lead to no end of troubles if two disconnected nodes
104
104
%% simultaneously ping each other.
105
 
%% Use this function in order to do it safe,
 
105
%% Use this function in order to do it safely.
106
106
%% It assumes a working global.erl which ensures a fully 
107
107
%% connected network.
108
108
%% Had the erlang runtime system been able to fully cope with 
109
109
%% the possibility of two simultaneous (unix) connects, this function would
110
110
%% merley  be lists:map({net_adm, ping}, [], Nodelist).
111
111
%% It is also assumed, that the same (identical) Nodelist is given to all
112
 
%% nodes which are to perform this call. (possibly simultaneously)
 
112
%% nodes which are to perform this call (possibly simultaneously).
113
113
%% Even this code has a flaw, and that is the case where two
114
114
%% nodes simultaneously and without *any* other already 
115
115
%% running nodes execute this code. :-(
149
149
 
150
150
%% This function polls a set of hosts according to a file called
151
151
%% .hosts.erlang that need to reside either in the current directory
152
 
%% or at your home directory ( The current dir is tried first )
 
152
%% or in your home directory. (The current directory is tried first.)
153
153
%% world() returns a list of all nodes on the network that can be 
154
 
%% found (including ourselves) obs. $HOME variable is inspected
 
154
%% found (including ourselves). Note: the $HOME variable is inspected.
155
155
%%
156
156
%% Added possibility to supply a list of hosts instead of reading
157
157
%% the .hosts.erlang file. 971016 patrik@erix.ericsson.se
197
197
            nil
198
198
    end.
199
199
 
200
 
do_ping([], _Host, _Verbose) ->
 
200
do_ping(Names, Host0, Verbose) ->
 
201
    case longshort(Host0) of
 
202
        ignored -> [];
 
203
        Host -> do_ping_1(Names, Host, Verbose)
 
204
    end.
 
205
 
 
206
do_ping_1([], _Host, _Verbose) ->
201
207
    [];
202
 
do_ping([{Name, _} | Rest], Host, Verbose) ->
 
208
do_ping_1([{Name, _} | Rest], Host, Verbose) ->
203
209
    Node = list_to_atom(Name ++ "@" ++ longshort(Host)),
204
210
    verbose(Verbose, "Pinging ~w -> ", [Node]),
205
211
    Result = ping(Node),
206
212
    verbose(Verbose, "~p\n", [Result]),
207
213
    case Result of
208
214
        pong ->
209
 
            [Node | do_ping(Rest, Host, Verbose)];
 
215
            [Node | do_ping_1(Rest, Host, Verbose)];
210
216
        pang ->
211
 
            do_ping(Rest, Host, Verbose)
 
217
            do_ping_1(Rest, Host, Verbose)
212
218
    end.
213
219
 
214
220
verbose(verbose, Format, Args) ->
218
224
 
219
225
longshort(Host) ->
220
226
    case net_kernel:longnames() of
221
 
        false ->
222
 
            uptodot(Host);
223
 
        true ->
224
 
            Host
 
227
        false -> uptodot(Host);
 
228
        true -> Host;
 
229
        ignored -> ignored
225
230
    end.
226
231
 
227
232
uptodot([$.|_]) -> [];