blob: 8965de78393482cd2ab3366d7fa5b97061898865 [file] [log] [blame]
% Internal SS7 route database keeping
% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
%
% Additional Permission under GNU AGPL version 3 section 7:
%
% If you modify this Program, or any covered work, by linking or
% combining it with runtime libraries of Erlang/OTP as released by
% Ericsson on http://www.erlang.org (or a modified version of these
% libraries), containing parts covered by the terms of the Erlang Public
% License (http://www.erlang.org/EPLICENSE), the licensors of this
% Program grant you additional permission to convey the resulting work
% without the need to license the runtime libraries of Erlang/OTP under
% the GNU Affero General Public License. Corresponding Source for a
% non-source form of such a combination shall include the source code
% for the parts of the runtime libraries of Erlang/OTP used as well as
% that of the covered work.
% this module is keeping the point code routing table for the MTP3 layer
% of the Omsocom SS7 protocol stack. Routes are created and deleted
% with create_route() and delete_route(), the arguments are
% * destination point code
% * point code mask
% * name of the linkset
%
% there is one function to actually make a routing decision: route_dpc/1
% with a single argument: the destination point code.
-module(ss7_routes).
-behaviour(gen_server).
-include_lib("osmo_ss7/include/mtp3.hrl").
% gen_fsm callbacks
-export([init/1, handle_call/3, handle_info/2, terminate/2, code_change/3]).
% our published API
-export([start_link/0]).
% client functions, may internally talk to our sccp_user server
-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}
linkset_name
}).
-record(sr_state, {
route_tbl
}).
% initialization code
start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [], [{debug, [trace]}]).
init(_Arg) ->
RouteTbl = ets:new(ss7_routes, [ordered_set, named_table,
{keypos, #ss7route.remote_pc_mask}]),
process_flag(trap_exit, true),
{ok, #sr_state{route_tbl = RouteTbl}}.
% client side API
% all write operations go through gen_server:call(), as only the ?MODULE
% process has permission to modify the table content
create_route(RemotePcIn, RemoteMask, LinksetName) ->
RemotePc = osmo_util:pointcode2int(RemotePcIn),
gen_server:call(?MODULE, {create_route, {RemotePc, RemoteMask, LinksetName}}).
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
route_dpc(DpcIn) ->
Dpc = osmo_util:pointcode2int(DpcIn),
% this was generated by ets:fun2ms() on the shell
Match = [{#ss7route{remote_pc_mask={'$1','$2'},linkset_name='$3'},
[{'==',{'band',Dpc,'$2'},'$1'}],
['$3']}],
case ets:select(ss7_routes, Match) of
[Name|_] ->
{ok, Name};
_ ->
{error, no_route}
end.
dump() ->
List = ets:tab2list(ss7_routes),
dump_routes(List).
dump_routes([]) ->
ok;
dump_routes([Head|Tail]) when is_record(Head, ss7route) ->
dump_single_route(Head),
dump_routes(Tail).
dump_single_route(#ss7route{remote_pc_mask = {Pc, Mask},
linkset_name = Name}) ->
PcTuple = osmo_util:pointcode_fmt(itu, Pc),
MaskTuple = osmo_util:pointcode_fmt(itu, Mask),
io:format("Dest PC ~p/~p -> Linkset ~p~n",
[PcTuple, MaskTuple, Name]).
% server side code
handle_call({create_route, {RemotePc, RemoteMask, Name}},
{_FromPid, _FromRef}, S) ->
#sr_state{route_tbl = Tbl} = S,
R = #ss7route{remote_pc_mask = {RemotePc, RemoteMask},
linkset_name = Name},
case ets:insert_new(Tbl, R) of
false ->
{reply, {error, ets_insert}, S};
_ ->
{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,
ets:delete(Tbl, {RemotePc, RemoteMask}),
{reply, ok, S}.
handle_info(Info, S) ->
error_logger:error_report(["unknown handle_info",
{module, ?MODULE},
{info, Info}, {state, S}]),
{noreply, S}.
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).