@@ -61,9 +61,11 @@ and `m:erl_prim_loader` in ERTS.
6161-behaviour (gen_server ).
6262
6363% % API functions.
64- -export ([start /1 , start_link /1 , add_slave /1 , delete_slave /1 ,
65- add_subnet /2 , delete_subnet /2 ,
66- which_slaves /0 ]).
64+ -export ([start /1 , start /2 ,
65+ start_link /1 , start_link /2 ,
66+ add_slave /1 , delete_slave /1 ,
67+ add_subnet /2 , delete_subnet /2 ,
68+ which_slaves /0 ]).
6769
6870% % Exports for testing (don't remove; tests suites depend on them).
6971-export ([would_be_booted /1 ]).
@@ -90,40 +92,85 @@ and `m:erl_prim_loader` in ERTS.
9092-define (single_addr_mask , {255 , 255 , 255 , 255 }).
9193
9294-doc """
93- Starts the boot server. `Slaves` is a list of IP addresses for hosts, which are
94- allowed to use this server as a boot server.
95+ The same as [`start(Slaves, #{})`](`start/2`).
9596""" .
9697-spec start (Slaves ) -> {'ok' , Pid } | {'error' , Reason } when
9798 Slaves :: [Host ],
9899 Host :: inet :ip_address () | inet :hostname (),
99100 Pid :: pid (),
100- Reason :: { 'badarg' , Slaves } .
101+ Reason :: any () .
101102
102103start (Slaves ) ->
103- case check_arg (Slaves ) of
104- {ok , AL } ->
105- gen_server :start ({local ,boot_server }, erl_boot_server , AL , []);
106- _ ->
107- {error , {badarg , Slaves }}
104+ start (Slaves , #{}).
105+
106+ -doc """
107+ Starts the boot server. `Slaves` is a list of IP addresses for hosts, which are
108+ allowed to use this server as a boot server. `Options` is a map with
109+ configuration options.
110+
111+ The boot server listening port can be configured with `listen_port`.
112+ If an empty map is provided, or `listen_port` is zero, then an ephemeral port
113+ is used.
114+ """ .
115+ -spec start (Slaves , Options ) -> {'ok' , Pid } | {'error' , Reason } when
116+ Slaves :: [Host ],
117+ Host :: inet :ip_address () | inet :hostname (),
118+ Options :: #{listen_port => inet :port_number ()},
119+ Pid :: pid (),
120+ Reason :: any ().
121+
122+ start (Slaves , Options ) ->
123+ case start_args (Slaves , Options ) of
124+ {ok , StartArgs } ->
125+ gen_server :start ({local ,boot_server }, erl_boot_server , StartArgs , []);
126+ {error , _ } = Error ->
127+ Error
108128 end .
109129
110130-doc """
111- Starts the boot server and links to the caller. This function is used to start
112- the server if it is included in a supervision tree.
131+ The same as [`start_link(Slaves, #{})`](`start_link/2`).
113132""" .
114133-spec start_link (Slaves ) -> {'ok' , Pid } | {'error' , Reason } when
115134 Slaves :: [Host ],
116135 Host :: inet :ip_address () | inet :hostname (),
117136 Pid :: pid (),
118- Reason :: { 'badarg' , Slaves } .
137+ Reason :: any () .
119138
120139start_link (Slaves ) ->
140+ start_link (Slaves , #{}).
141+
142+ -doc """
143+ The same as [`start(Slaves, Options)`](`start/2`), but it also links to the
144+ caller.
145+ """ .
146+ -spec start_link (Slaves , Options ) -> {'ok' , Pid } | {'error' , Reason } when
147+ Slaves :: [Host ],
148+ Host :: inet :ip_address () | inet :hostname (),
149+ Options :: #{listen_port => inet :port_number ()},
150+ Pid :: pid (),
151+ Reason :: any ().
152+
153+ start_link (Slaves , Options ) ->
154+ case start_args (Slaves , Options ) of
155+ {ok , StartArgs } ->
156+ gen_server :start_link ({local ,boot_server }, erl_boot_server , StartArgs , []);
157+ {error , _ } = Error ->
158+ Error
159+ end .
160+
161+ start_args (Slaves , Options ) ->
121162 case check_arg (Slaves ) of
122- {ok , AL } ->
123- gen_server :start_link ({local ,boot_server },
124- erl_boot_server , AL , []);
125- _ ->
126- {error , {badarg , Slaves }}
163+ {ok , Arg } ->
164+ case check_options (Options ) of
165+ true ->
166+ NewOptions = with_default_options (Options ),
167+ ListenPort = maps :get (listen_port , NewOptions ),
168+ {ok , #{slaves => Arg , listen_port => ListenPort }};
169+ false ->
170+ {error , {badarg , Options }}
171+ end ;
172+ _ ->
173+ {error , {badarg , Slaves }}
127174 end .
128175
129176check_arg (Slaves ) ->
@@ -141,6 +188,18 @@ check_arg([], Result) ->
141188check_arg (_ , _Result ) ->
142189 error .
143190
191+ check_options (Options ) when is_map (Options ) ->
192+ lists :all (fun valid_option /1 , maps :to_list (Options ));
193+ check_options (_ ) ->
194+ false .
195+
196+ valid_option ({listen_port , Port }) when is_integer (Port ) -> true ;
197+ valid_option ({_ , _ }) -> false .
198+
199+ with_default_options (Options ) ->
200+ DefaultOptions = #{listen_port => 0 },
201+ maps :merge (DefaultOptions , Options ).
202+
144203-doc " Adds a `Slave` node to the list of allowed slave hosts." .
145204-spec add_slave (Slave ) -> 'ok' | {'error' , Reason } when
146205 Slave :: Host ,
@@ -228,11 +287,14 @@ member_address(_, []) ->
228287% % ------------------------------------------------------------
229288
230289-doc false .
231- -spec init ([atom ()]) -> {'ok' , state ()}.
290+ -spec init (#{slaves := list (),
291+ listen_port := inet :port_number ()})
292+ -> {'ok' , state ()}.
232293
233- init (Slaves ) ->
294+ init (#{slaves := Slaves ,
295+ listen_port := ListenPort }) ->
234296 {ok , U } = gen_udp :open (? EBOOT_PORT , []),
235- {ok , L } = gen_tcp :listen (0 , [binary ,{packet ,4 }]),
297+ {ok , L } = gen_tcp :listen (ListenPort , [binary ,{packet ,4 }]),
236298 {ok , Port } = inet :port (L ),
237299 {ok , UPort } = inet :port (U ),
238300 Ref = make_ref (),
0 commit comments