blob: 8965de78393482cd2ab3366d7fa5b97061898865 [file] [log] [blame]
Harald Welteb8bfc4e2011-10-11 18:49:59 +02001% Internal SS7 route database keeping
2
Harald Welted44e3ea2013-09-08 21:33:10 +02003% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
Harald Welteb8bfc4e2011-10-11 18:49:59 +02004%
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/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
Harald Welteb8bfc4e2011-10-11 18:49:59 +020033
Harald Welte9bfab7c2011-10-12 00:02:42 +020034
35% this module is keeping the point code routing table for the MTP3 layer
36% of the Omsocom SS7 protocol stack. Routes are created and deleted
37% with create_route() and delete_route(), the arguments are
38% * destination point code
39% * point code mask
40% * name of the linkset
41%
42% there is one function to actually make a routing decision: route_dpc/1
43% with a single argument: the destination point code.
44
Harald Welteb8bfc4e2011-10-11 18:49:59 +020045-module(ss7_routes).
46-behaviour(gen_server).
47
48-include_lib("osmo_ss7/include/mtp3.hrl").
49
50% gen_fsm callbacks
51-export([init/1, handle_call/3, handle_info/2, terminate/2, code_change/3]).
52
53% our published API
54-export([start_link/0]).
55
56% client functions, may internally talk to our sccp_user server
Harald Welted44e3ea2013-09-08 21:33:10 +020057-export([create_route/3, delete_route/3, flush_routes/0]).
Harald Welteb8bfc4e2011-10-11 18:49:59 +020058-export([dump/0]).
59-export([route_dpc/1]).
Harald Welted44e3ea2013-09-08 21:33:10 +020060-export([reload_config/0]).
Harald Welteb8bfc4e2011-10-11 18:49:59 +020061
62-record(ss7route, {
63 remote_pc_mask, % {remote_pc, remote_pc_mask}
64 linkset_name
65}).
66
67-record(sr_state, {
68 route_tbl
69}).
70
71% initialization code
72
73start_link() ->
74 gen_server:start_link({local, ?MODULE}, ?MODULE, [], [{debug, [trace]}]).
75
76init(_Arg) ->
77 RouteTbl = ets:new(ss7_routes, [ordered_set, named_table,
78 {keypos, #ss7route.remote_pc_mask}]),
79 process_flag(trap_exit, true),
80 {ok, #sr_state{route_tbl = RouteTbl}}.
81
82% client side API
83
84% all write operations go through gen_server:call(), as only the ?MODULE
85% process has permission to modify the table content
86
Harald Welte4608ba12011-12-08 12:10:34 +010087create_route(RemotePcIn, RemoteMask, LinksetName) ->
88 RemotePc = osmo_util:pointcode2int(RemotePcIn),
Harald Welteb8bfc4e2011-10-11 18:49:59 +020089 gen_server:call(?MODULE, {create_route, {RemotePc, RemoteMask, LinksetName}}).
90
Harald Welte4608ba12011-12-08 12:10:34 +010091delete_route(RemotePcIn, RemoteMask, LinksetName) ->
92 RemotePc = osmo_util:pointcode2int(RemotePcIn),
Harald Welteb8bfc4e2011-10-11 18:49:59 +020093 gen_server:call(?MODULE, {delete_route, {RemotePc, RemoteMask, LinksetName}}).
94
Harald Welted44e3ea2013-09-08 21:33:10 +020095flush_routes() ->
96 gen_server:call(?MODULE, flush_routes).
97
Harald Welteb8bfc4e2011-10-11 18:49:59 +020098% the lookup functions can directly use the ets named_table from within
99% the client process, no need to go through a synchronous IPC
100
Harald Welte19350ad2011-12-08 12:05:34 +0100101route_dpc(DpcIn) ->
102 Dpc = osmo_util:pointcode2int(DpcIn),
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200103 % this was generated by ets:fun2ms() on the shell
104 Match = [{#ss7route{remote_pc_mask={'$1','$2'},linkset_name='$3'},
105 [{'==',{'band',Dpc,'$2'},'$1'}],
106 ['$3']}],
107 case ets:select(ss7_routes, Match) of
108 [Name|_] ->
109 {ok, Name};
110 _ ->
111 {error, no_route}
112 end.
113
114dump() ->
115 List = ets:tab2list(ss7_routes),
116 dump_routes(List).
117
118dump_routes([]) ->
119 ok;
120dump_routes([Head|Tail]) when is_record(Head, ss7route) ->
121 dump_single_route(Head),
122 dump_routes(Tail).
123
124dump_single_route(#ss7route{remote_pc_mask = {Pc, Mask},
125 linkset_name = Name}) ->
Harald Welte9bfab7c2011-10-12 00:02:42 +0200126 PcTuple = osmo_util:pointcode_fmt(itu, Pc),
127 MaskTuple = osmo_util:pointcode_fmt(itu, Mask),
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200128 io:format("Dest PC ~p/~p -> Linkset ~p~n",
Harald Welte9bfab7c2011-10-12 00:02:42 +0200129 [PcTuple, MaskTuple, Name]).
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200130
131% server side code
132
133handle_call({create_route, {RemotePc, RemoteMask, Name}},
134 {_FromPid, _FromRef}, S) ->
135 #sr_state{route_tbl = Tbl} = S,
136 R = #ss7route{remote_pc_mask = {RemotePc, RemoteMask},
137 linkset_name = Name},
138 case ets:insert_new(Tbl, R) of
139 false ->
140 {reply, {error, ets_insert}, S};
141 _ ->
142 {reply, ok, S}
143 end;
144
Harald Welted44e3ea2013-09-08 21:33:10 +0200145handle_call(flush_routes, {_FromPid, _FromRef}, S) ->
146 #sr_state{route_tbl = Tbl} = S,
147 ets:delete_all_objects(Tbl),
148 {reply, ok, S};
149
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200150handle_call({delete_route, {RemotePc, RemoteMask, _Name}},
151 {_FromPid, _FromRef}, S) ->
152 #sr_state{route_tbl = Tbl} = S,
153 ets:delete(Tbl, {RemotePc, RemoteMask}),
154 {reply, ok, S}.
155
156handle_info(Info, S) ->
157 error_logger:error_report(["unknown handle_info",
158 {module, ?MODULE},
159 {info, Info}, {state, S}]),
160 {noreply, S}.
161
162terminate(Reason, _S) ->
163 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
164 ok.
165
Harald Welted44e3ea2013-09-08 21:33:10 +0200166
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200167code_change(_OldVsn, State, _Extra) ->
168 {ok, State}.
Harald Welted44e3ea2013-09-08 21:33:10 +0200169
170reconfig_route({Dpc, Mask, Dest}) ->
171 case create_route(Dpc, Mask, Dest) of
172 ok -> true;
173 _ -> false
174 end.
175
176reload_config() ->
177 flush_routes(),
178 Routes = osmo_util:get_env(osmo_ss7, routes, []),
179 lists:all(fun reconfig_route/1, Routes).