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

« back to all changes in this revision

Viewing changes to lib/kernel/src/erl_boot_server.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
%% A simple boot_server at a CP.
19
20
%%
24
25
-module(erl_boot_server).
25
26
 
26
27
-include("inet_boot.hrl").
 
28
 
27
29
-behaviour(gen_server).
28
30
 
29
31
%% API functions.
42
44
-record(state, 
43
45
        {
44
46
          priority = 0,  %% priority of this server
45
 
          version = "",  %% Version handled i.e "4.5.3" etc
 
47
          version = ""   :: string(),   %% Version handled i.e "4.5.3" etc
46
48
          udp_sock,      %% listen port for broadcase requests
47
49
          udp_port,      %% port number must be ?EBOOT_PORT!
48
50
          listen_sock,   %% listen sock for incoming file requests
49
51
          listen_port,   %% listen port number
50
52
          slaves,        %% list of accepted ip addresses
51
 
          bootp,         %% boot process
 
53
          bootp          :: pid(),      %% boot process
52
54
          prim_state     %% state for efile code loader
53
55
         }).
54
56
 
55
57
-define(single_addr_mask, {255, 255, 255, 255}).
56
58
 
57
 
-type(ip4_address() :: {0..255,0..255,0..255,0..255}).
 
59
-type ip4_address() :: {0..255,0..255,0..255,0..255}.
58
60
 
59
 
-spec(start/1 :: (Slaves :: [atom()]) -> 
60
 
        {'ok', pid()} | {'error', any()}).
 
61
-spec start(Slaves :: [atom()]) -> {'ok', pid()} | {'error', any()}.
61
62
 
62
63
start(Slaves) ->
63
64
    case check_arg(Slaves) of
64
 
        {ok,AL} ->
 
65
        {ok, AL} ->
65
66
            gen_server:start({local,boot_server}, erl_boot_server, AL, []);
66
67
        _ ->
67
68
            {error, {badarg, Slaves}}
68
69
    end.
69
70
 
70
 
-spec(start_link/1 :: (Slaves :: [atom()]) ->
71
 
        {'ok', pid()} | {'error', any()}).
 
71
-spec start_link(Slaves :: [atom()]) -> {'ok', pid()} | {'error', any()}.
72
72
 
73
73
start_link(Slaves) ->
74
74
    case check_arg(Slaves) of
75
 
        {ok,AL} ->
 
75
        {ok, AL} ->
76
76
            gen_server:start_link({local,boot_server},
77
77
                                  erl_boot_server, AL, []);
78
78
        _ ->
94
94
check_arg(_, _Result) ->
95
95
    error.
96
96
 
97
 
-spec(add_slave/1 :: (Slave :: atom()) ->
98
 
        'ok' | {'error', any()}).
 
97
-spec add_slave(Slave :: atom()) -> 'ok' | {'error', any()}.
99
98
 
100
99
add_slave(Slave) ->
101
100
    case inet:getaddr(Slave, inet) of
105
104
            {error, {badarg, Slave}}
106
105
    end.
107
106
 
108
 
-spec(delete_slave/1 :: (Slave :: atom()) ->
109
 
        'ok' | {'error', any()}).
 
107
-spec delete_slave(Slave :: atom()) -> 'ok' | {'error', any()}.
110
108
 
111
109
delete_slave(Slave) ->
112
110
    case inet:getaddr(Slave, inet) of
116
114
            {error, {badarg, Slave}}
117
115
    end.
118
116
 
119
 
-spec(add_subnet/2 :: (
120
 
        Mask :: ip4_address(), 
121
 
        Addr :: ip4_address()) -> 
122
 
        {'error', any()} | 'ok').  
 
117
-spec add_subnet(Mask :: ip4_address(), Addr :: ip4_address()) ->
 
118
        'ok' | {'error', any()}.
123
119
 
124
120
add_subnet(Mask, Addr) when is_tuple(Mask), is_tuple(Addr) ->
125
121
    case member_address(Addr, [{Mask, Addr}]) of
129
125
            {error, empty_subnet}
130
126
    end.
131
127
 
132
 
-spec(delete_subnet/2 :: (
133
 
        Mask :: ip4_address(), 
134
 
        Addr :: ip4_address()) -> 
135
 
        'ok').  
 
128
-spec delete_subnet(Mask :: ip4_address(), Addr :: ip4_address()) -> 'ok'.
136
129
 
137
130
delete_subnet(Mask, Addr) when is_tuple(Mask), is_tuple(Addr) ->
138
131
    gen_server:call(boot_server, {delete, {Mask, Addr}}).
139
132
 
140
 
-spec(which_slaves/0 :: () ->
141
 
        [atom()]).
 
133
-spec which_slaves() -> [atom()].
142
134
 
143
135
which_slaves() ->
144
136
    gen_server:call(boot_server, which).
176
168
init(Slaves) ->
177
169
    {ok, U} = gen_udp:open(?EBOOT_PORT, []),
178
170
    {ok, L} = gen_tcp:listen(0, [binary,{packet,4}]),
179
 
    {ok,Port} = inet:port(L),
180
 
    {ok,UPort} = inet:port(U),
 
171
    {ok, Port} = inet:port(L),
 
172
    {ok, UPort} = inet:port(U),
181
173
    Ref = make_ref(),
182
174
    Pid = proc_lib:spawn_link(?MODULE, boot_init, [Ref]),
183
175
    gen_tcp:controlling_process(L, Pid),
197
189
handle_call({add,Address}, _, S0) ->
198
190
    Slaves = ordsets:add_element(Address, S0#state.slaves),
199
191
    S0#state.bootp ! {slaves, Slaves},
200
 
    {reply, ok, S0#state { slaves = Slaves}};
 
192
    {reply, ok, S0#state{slaves = Slaves}};
201
193
handle_call({delete,Address}, _, S0) ->
202
194
    Slaves = ordsets:del_element(Address, S0#state.slaves),
203
195
    S0#state.bootp ! {slaves, Slaves},
204
 
    {reply, ok, S0#state { slaves = Slaves }};
 
196
    {reply, ok, S0#state{slaves = Slaves}};
205
197
handle_call(which, _, S0) ->
206
198
    {reply, ordsets:to_list(S0#state.slaves), S0}.
207
199
 
259
251
 
260
252
boot_main(Listen) ->
261
253
    Tag = make_ref(),
262
 
    Pid = proc_lib:spawn_link(?MODULE,boot_accept,[self(),Listen,Tag]),
 
254
    Pid = proc_lib:spawn_link(?MODULE, boot_accept, [self(), Listen, Tag]),
263
255
    boot_main(Listen, Tag, Pid).
264
256
 
265
257
boot_main(Listen, Tag, Pid) ->
281
273
    Server ! {Tag, continue},
282
274
    case Reply of
283
275
        {ok, Socket} ->
284
 
            {ok,{IP,_Port}} = inet:peername(Socket),
 
276
            {ok, {IP, _Port}} = inet:peername(Socket),
285
277
            true = member_address(IP, which_slaves()),
286
278
            PS = erl_prim_loader:prim_init(),
287
279
            boot_loop(Socket, PS)