permit configuration of links, linksets and routes in app config

Links, Linksets and routes can now be configured in the applicaiton
configuration file.
This commit is contained in:
Harald Welte 2013-09-08 21:33:10 +02:00
parent bd88eb1b41
commit d44e3ea6de
3 changed files with 61 additions and 7 deletions

View File

@ -8,7 +8,9 @@
-export([reload_config/0]).
start(normal, StartArgs) ->
supervisor:start_link({local, osmo_ss7_sup}, osmo_ss7_sup, StartArgs).
{ok, Pid} = supervisor:start_link({local, osmo_ss7_sup}, osmo_ss7_sup, StartArgs),
reload_config(),
{ok, Pid}.
start_phase(_Phase, _StartType, _PhaseArgs) ->
@ -27,5 +29,7 @@ config_change(_Changed, _New, _Removed) ->
reload_config() ->
osmo_util:reload_config(),
% FIXME: do something
% fixme: why not in config/change/3 ?
ss7_links:reload_config(),
ss7_routes:reload_config(),
ok.

View File

@ -1,6 +1,6 @@
% Internal SCCP link database keeping
% Internal SS7 link database keeping
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
@ -36,13 +36,14 @@
-include_lib("osmo_ss7/include/mtp3.hrl").
-include_lib("osmo_ss7/include/osmo_util.hrl").
-include_lib("osmo_ss7/include/osmo_ss7.hrl").
% gen_fsm callbacks
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
terminate/2, code_change/3]).
% our published API
-export([start_link/0]).
-export([start_link/0, reload_config/0]).
% client functions, may internally talk to our sccp_user server
-export([register_linkset/3, unregister_linkset/1]).
@ -471,3 +472,31 @@ role2sctp_role(asp) ->
active;
role2sctp_role(sg) ->
passive.
to_peer({Ip, Port, Pointcode}) ->
#sigtran_peer{ip=Ip, port=Port, point_code=Pointcode}.
reconfig_linkset({Name, LocalPC, RemotePC}) ->
unregister_linkset(Name),
case register_linkset(LocalPC, RemotePC, Name) of
ok -> true;
_ -> false
end.
reconfig_link({Name, {Lset, Sls}, Type, Local, Remote}) ->
% FIXME: not relaod safe!!
L = #sigtran_link{type=Type, name=Name, linkset_name=Lset,
sls=Sls, local=to_peer(Local), remote=to_peer(Remote)},
case osmo_ss7_sup:add_mtp_link(L) of
{ok, _, _} -> true;
{ok, _} -> true;
{error, _} -> false
end.
reload_config() ->
Linksets = osmo_util:get_env(osmo_ss7, linksets, []),
LinksetsRes = lists:all(fun reconfig_linkset/1, Linksets),
Links = osmo_util:get_env(osmo_ss7, links, []),
LinksRes = lists:all(fun reconfig_link/1, Links),
LinksetsRes and LinksRes.

View File

@ -1,6 +1,6 @@
% Internal SS7 route database keeping
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
@ -54,9 +54,10 @@
-export([start_link/0]).
% client functions, may internally talk to our sccp_user server
-export([create_route/3, delete_route/3]).
-export([create_route/3, delete_route/3, flush_routes/0]).
-export([dump/0]).
-export([route_dpc/1]).
-export([reload_config/0]).
-record(ss7route, {
remote_pc_mask, % {remote_pc, remote_pc_mask}
@ -91,6 +92,9 @@ delete_route(RemotePcIn, RemoteMask, LinksetName) ->
RemotePc = osmo_util:pointcode2int(RemotePcIn),
gen_server:call(?MODULE, {delete_route, {RemotePc, RemoteMask, LinksetName}}).
flush_routes() ->
gen_server:call(?MODULE, flush_routes).
% the lookup functions can directly use the ets named_table from within
% the client process, no need to go through a synchronous IPC
@ -138,6 +142,11 @@ handle_call({create_route, {RemotePc, RemoteMask, Name}},
{reply, ok, S}
end;
handle_call(flush_routes, {_FromPid, _FromRef}, S) ->
#sr_state{route_tbl = Tbl} = S,
ets:delete_all_objects(Tbl),
{reply, ok, S};
handle_call({delete_route, {RemotePc, RemoteMask, _Name}},
{_FromPid, _FromRef}, S) ->
#sr_state{route_tbl = Tbl} = S,
@ -154,5 +163,17 @@ terminate(Reason, _S) ->
io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
ok.
code_change(_OldVsn, State, _Extra) ->
{ok, State}.
reconfig_route({Dpc, Mask, Dest}) ->
case create_route(Dpc, Mask, Dest) of
ok -> true;
_ -> false
end.
reload_config() ->
flush_routes(),
Routes = osmo_util:get_env(osmo_ss7, routes, []),
lists:all(fun reconfig_route/1, Routes).