summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--ebin/osmo_ss7.app1
-rw-r--r--src/osmo_ss7_sup.erl4
-rw-r--r--src/ss7_links.erl51
-rw-r--r--src/ss7_routes.erl128
4 files changed, 173 insertions, 11 deletions
diff --git a/ebin/osmo_ss7.app b/ebin/osmo_ss7.app
index f3d5f05..ee031f7 100644
--- a/ebin/osmo_ss7.app
+++ b/ebin/osmo_ss7.app
@@ -11,6 +11,7 @@
sccp_codec,
osmo_ss7_sup, osmo_ss7_app,
ss7_links, ss7_link_m3ua, ss7_link_ipa_client,
+ ss7_routes,
ss7_service_dump,
osmo_ss7_gtt,
osmo_ss7_pcap
diff --git a/src/osmo_ss7_sup.erl b/src/osmo_ss7_sup.erl
index 2e34b41..ed31cb5 100644
--- a/src/osmo_ss7_sup.erl
+++ b/src/osmo_ss7_sup.erl
@@ -31,7 +31,9 @@ start_link() ->
init(Args) ->
LinksChild = {ss7_links, {ss7_links, start_link, []},
permanent, 2000, worker, [ss7_links]},
- {ok,{{one_for_one,60,600}, [LinksChild]}}.
+ RouteChild = {ss7_routes, {ss7_routes, start_link, []},
+ permanent, 2000, worker, [ss7_routes]},
+ {ok,{{one_for_one,60,600}, [LinksChild, RouteChild]}}.
% Add a m3ua link to this supervisor
add_mtp_link(L=#sigtran_link{type = m3ua, name = Name,
diff --git a/src/ss7_links.erl b/src/ss7_links.erl
index 5e98b3b..75617f5 100644
--- a/src/ss7_links.erl
+++ b/src/ss7_links.erl
@@ -39,20 +39,20 @@
-record(slink, {
key, % {linkset_name, sls}
- name,
- linkset_name,
+ name, % name of the link
+ linkset_name, % name of the linkset to which we belong
sls,
- user_pid,
- state
+ user_pid, % Pid handling MTP-TRANSFER primitives
+ state % (down | up | active)
}).
-record(slinkset, {
- name,
- local_pc,
- remote_pc,
+ name, % name of the linkset
+ local_pc, % local point code
+ remote_pc, % remote point code
user_pid,
- state,
- links
+ state, % (down | up_inactive | active)
+ active_sls % list of Sls of currently active links
}).
-record(service, {
@@ -218,7 +218,8 @@ handle_call({register_linkset, {LocalPc, RemotePc, Name}},
{FromPid, _FromRef}, S) ->
#su_state{linkset_tbl = Tbl} = S,
Ls = #slinkset{local_pc = LocalPc, remote_pc = RemotePc,
- name = Name, user_pid = FromPid},
+ name = Name, user_pid = FromPid,
+ state = down, active_sls=[]},
case ets:insert_new(Tbl, Ls) of
false ->
{reply, {error, ets_insert}, S};
@@ -270,6 +271,7 @@ handle_call({set_link_state, {LsName, Sls, State}}, {FromPid, _}, S) ->
[Link] ->
NewLink = Link#slink{state = State},
ets:insert(LinkTbl, NewLink),
+ propagate_linkstate_to_linkset(LsName, Sls, State),
{reply, ok, S}
end;
@@ -322,3 +324,32 @@ terminate(Reason, _S) ->
code_change(_OldVsn, State, _Extra) ->
{ok, State}.
+
+% update the active_sls state in a linkset after a link state chg
+propagate_linkstate_to_linkset(LsName, Sls, State) ->
+ case ets:lookup(ss7_linksets, LsName) of
+ [Ls = #slinkset{}] ->
+ #slinkset{active_sls = ActSls, remote_pc = Dpc} = Ls,
+ case State of
+ active ->
+ % add Sls to list (unique)
+ ActSls2 = lists:usort([Sls|ActSls]);
+ _ ->
+ % del Sls from list
+ ActSls2 = lists:delete(Sls, ActSls)
+ end,
+ % compute the linkstate state
+ case ActSls2 of
+ [] ->
+ LsState = up_inactive,
+ ss7_routes:delete_route(Dpc, 16#ffff, LsName);
+ _ ->
+ LsState = active,
+ ss7_routes:create_route(Dpc, 16#ffff, LsName)
+ end,
+ ets:insert(ss7_linksets,
+ Ls#slinkset{active_sls = ActSls2,
+ state = LsState});
+ _ ->
+ {error, ets_lookup}
+ end.
diff --git a/src/ss7_routes.erl b/src/ss7_routes.erl
new file mode 100644
index 0000000..70fd5c9
--- /dev/null
+++ b/src/ss7_routes.erl
@@ -0,0 +1,128 @@
+% Internal SS7 route database keeping
+
+% (C) 2011 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/>.
+
+-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]).
+-export([dump/0]).
+-export([route_dpc/1]).
+
+-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(RemotePc, RemoteMask, LinksetName) ->
+ gen_server:call(?MODULE, {create_route, {RemotePc, RemoteMask, LinksetName}}).
+
+delete_route(RemotePc, RemoteMask, LinksetName) ->
+ gen_server:call(?MODULE, {delete_route, {RemotePc, RemoteMask, LinksetName}}).
+
+% 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(Dpc) ->
+ % 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}) ->
+ io:format("Dest PC ~p/~p -> Linkset ~p~n",
+ [Pc, Mask, 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({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}.