blob: 6aac9517e1985b0514c9236a5cbae3ef8d87c492 [file] [log] [blame]
Harald Welteb8bfc4e2011-10-11 18:49:59 +02001% Internal SS7 route database keeping
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
19
Harald Welte9bfab7c2011-10-12 00:02:42 +020020
21% this module is keeping the point code routing table for the MTP3 layer
22% of the Omsocom SS7 protocol stack. Routes are created and deleted
23% with create_route() and delete_route(), the arguments are
24% * destination point code
25% * point code mask
26% * name of the linkset
27%
28% there is one function to actually make a routing decision: route_dpc/1
29% with a single argument: the destination point code.
30
Harald Welteb8bfc4e2011-10-11 18:49:59 +020031-module(ss7_routes).
32-behaviour(gen_server).
33
34-include_lib("osmo_ss7/include/mtp3.hrl").
35
36% gen_fsm callbacks
37-export([init/1, handle_call/3, handle_info/2, terminate/2, code_change/3]).
38
39% our published API
40-export([start_link/0]).
41
42% client functions, may internally talk to our sccp_user server
43-export([create_route/3, delete_route/3]).
44-export([dump/0]).
45-export([route_dpc/1]).
46
47-record(ss7route, {
48 remote_pc_mask, % {remote_pc, remote_pc_mask}
49 linkset_name
50}).
51
52-record(sr_state, {
53 route_tbl
54}).
55
56% initialization code
57
58start_link() ->
59 gen_server:start_link({local, ?MODULE}, ?MODULE, [], [{debug, [trace]}]).
60
61init(_Arg) ->
62 RouteTbl = ets:new(ss7_routes, [ordered_set, named_table,
63 {keypos, #ss7route.remote_pc_mask}]),
64 process_flag(trap_exit, true),
65 {ok, #sr_state{route_tbl = RouteTbl}}.
66
67% client side API
68
69% all write operations go through gen_server:call(), as only the ?MODULE
70% process has permission to modify the table content
71
72create_route(RemotePc, RemoteMask, LinksetName) ->
73 gen_server:call(?MODULE, {create_route, {RemotePc, RemoteMask, LinksetName}}).
74
75delete_route(RemotePc, RemoteMask, LinksetName) ->
76 gen_server:call(?MODULE, {delete_route, {RemotePc, RemoteMask, LinksetName}}).
77
78% the lookup functions can directly use the ets named_table from within
79% the client process, no need to go through a synchronous IPC
80
Harald Welte19350ad2011-12-08 12:05:34 +010081route_dpc(DpcIn) ->
82 Dpc = osmo_util:pointcode2int(DpcIn),
Harald Welteb8bfc4e2011-10-11 18:49:59 +020083 % this was generated by ets:fun2ms() on the shell
84 Match = [{#ss7route{remote_pc_mask={'$1','$2'},linkset_name='$3'},
85 [{'==',{'band',Dpc,'$2'},'$1'}],
86 ['$3']}],
87 case ets:select(ss7_routes, Match) of
88 [Name|_] ->
89 {ok, Name};
90 _ ->
91 {error, no_route}
92 end.
93
94dump() ->
95 List = ets:tab2list(ss7_routes),
96 dump_routes(List).
97
98dump_routes([]) ->
99 ok;
100dump_routes([Head|Tail]) when is_record(Head, ss7route) ->
101 dump_single_route(Head),
102 dump_routes(Tail).
103
104dump_single_route(#ss7route{remote_pc_mask = {Pc, Mask},
105 linkset_name = Name}) ->
Harald Welte9bfab7c2011-10-12 00:02:42 +0200106 PcTuple = osmo_util:pointcode_fmt(itu, Pc),
107 MaskTuple = osmo_util:pointcode_fmt(itu, Mask),
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200108 io:format("Dest PC ~p/~p -> Linkset ~p~n",
Harald Welte9bfab7c2011-10-12 00:02:42 +0200109 [PcTuple, MaskTuple, Name]).
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200110
111% server side code
112
113handle_call({create_route, {RemotePc, RemoteMask, Name}},
114 {_FromPid, _FromRef}, S) ->
115 #sr_state{route_tbl = Tbl} = S,
116 R = #ss7route{remote_pc_mask = {RemotePc, RemoteMask},
117 linkset_name = Name},
118 case ets:insert_new(Tbl, R) of
119 false ->
120 {reply, {error, ets_insert}, S};
121 _ ->
122 {reply, ok, S}
123 end;
124
125handle_call({delete_route, {RemotePc, RemoteMask, _Name}},
126 {_FromPid, _FromRef}, S) ->
127 #sr_state{route_tbl = Tbl} = S,
128 ets:delete(Tbl, {RemotePc, RemoteMask}),
129 {reply, ok, S}.
130
131handle_info(Info, S) ->
132 error_logger:error_report(["unknown handle_info",
133 {module, ?MODULE},
134 {info, Info}, {state, S}]),
135 {noreply, S}.
136
137terminate(Reason, _S) ->
138 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
139 ok.
140
141code_change(_OldVsn, State, _Extra) ->
142 {ok, State}.