blob: 499b91817872391791a70b5457b061dcab5ba224 [file] [log] [blame]
Harald Weltec6e466e2011-10-10 14:03:50 +02001% Internal SCCP link 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
20-module(ss7_links).
21-behaviour(gen_server).
22
23-include_lib("osmo_ss7/include/mtp3.hrl").
Harald Welte7dadde82011-10-19 13:40:39 +020024-include_lib("osmo_ss7/include/osmo_util.hrl").
Harald Weltec6e466e2011-10-10 14:03:50 +020025
26% gen_fsm callbacks
27-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
28 terminate/2, code_change/3]).
29
30% our published API
31-export([start_link/0]).
32
33% client functions, may internally talk to our sccp_user server
34-export([register_linkset/3, unregister_linkset/1]).
35-export([register_link/3, unregister_link/2, set_link_state/3]).
36-export([bind_service/2, unbind_service/1]).
37
Harald Welte9b5ea3e2011-12-08 14:09:34 +010038-export([get_pid_for_link/2, get_pid_for_dpc_sls/2,
39 mtp3_tx/1, mtp3_tx/2,
Harald Welte7dadde82011-10-19 13:40:39 +020040 get_linkset_for_dpc/1, get_opc_for_linkset/1, is_pc_local/1,
41 get_user_pid_for_service/1, mtp3_rx/1, dump/0]).
Harald Weltec6e466e2011-10-10 14:03:50 +020042
43-record(slink, {
44 key, % {linkset_name, sls}
Harald Welteb8bfc4e2011-10-11 18:49:59 +020045 name, % name of the link
46 linkset_name, % name of the linkset to which we belong
Harald Weltec6e466e2011-10-10 14:03:50 +020047 sls,
Harald Welteb8bfc4e2011-10-11 18:49:59 +020048 user_pid, % Pid handling MTP-TRANSFER primitives
49 state % (down | up | active)
Harald Weltec6e466e2011-10-10 14:03:50 +020050}).
51
52-record(slinkset, {
Harald Welteb8bfc4e2011-10-11 18:49:59 +020053 name, % name of the linkset
54 local_pc, % local point code
55 remote_pc, % remote point code
Harald Weltec6e466e2011-10-10 14:03:50 +020056 user_pid,
Harald Welteb8bfc4e2011-10-11 18:49:59 +020057 state, % (down | up_inactive | active)
58 active_sls % list of Sls of currently active links
Harald Weltec6e466e2011-10-10 14:03:50 +020059}).
60
61-record(service, {
62 name,
63 service_nr,
64 user_pid
65}).
66
67-record(su_state, {
68 linkset_tbl,
69 link_tbl,
70 service_tbl
71}).
72
73
74% initialization code
75
76start_link() ->
77 gen_server:start_link({local, ?MODULE}, ?MODULE, [], [{debug, [trace]}]).
78
79init(_Arg) ->
80 LinksetTbl = ets:new(ss7_linksets, [ordered_set, named_table,
81 {keypos, #slinkset.name}]),
82 ServiceTbl = ets:new(mtp3_services, [ordered_set, named_table,
83 {keypos, #service.service_nr}]),
84
85 % create a named table so we can query without reference directly
86 % within client/caller process
87 LinkTbl = ets:new(ss7_link_table, [ordered_set, named_table,
88 {keypos, #slink.key}]),
Harald Welte1ea44692011-10-10 19:19:13 +020089 process_flag(trap_exit, true),
Harald Weltec6e466e2011-10-10 14:03:50 +020090 {ok, #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl,
91 service_tbl = ServiceTbl}}.
92
93% client side API
94
95% all write operations go through gen_server:call(), as only the ?MODULE
96% process has permission to modify the table content
97
98register_linkset(LocalPc, RemotePc, Name) ->
99 gen_server:call(?MODULE, {register_linkset, {LocalPc, RemotePc, Name}}).
100
101unregister_linkset(Name) ->
102 gen_server:call(?MODULE, {unregister_linkset, {Name}}).
103
104register_link(LinksetName, Sls, Name) ->
105 gen_server:call(?MODULE, {register_link, {LinksetName, Sls, Name}}).
106
107unregister_link(LinksetName, Sls) ->
108 gen_server:call(?MODULE, {unregister_link, {LinksetName, Sls}}).
109
110set_link_state(LinksetName, Sls, State) ->
111 gen_server:call(?MODULE, {set_link_state, {LinksetName, Sls, State}}).
112
113% bind a service (such as ISUP, SCCP) to the MTP3 link manager
114bind_service(ServiceNum, ServiceName) ->
115 gen_server:call(?MODULE, {bind_service, {ServiceNum, ServiceName}}).
116
117% unbind a service (such as ISUP, SCCP) from the MTP3 link manager
118unbind_service(ServiceNum) ->
119 gen_server:call(?MODULE, {unbind_service, {ServiceNum}}).
120
121% the lookup functions can directly use the ets named_table from within
122% the client process, no need to go through a synchronous IPC
123
Harald Welte7dadde82011-10-19 13:40:39 +0200124get_user_pid_for_service(Service) when is_integer(Service) ->
125 case ets:lookup(mtp3_services, Service) of
126 [#service{user_pid=Pid}] ->
127 {ok, Pid};
128 [] ->
129 {error, no_such_service}
130 end.
131
Harald Welte805fac42011-10-12 17:17:55 +0200132get_pid_for_link(LinksetName, Sls) when is_list(LinksetName), is_integer(Sls) ->
Harald Weltec6e466e2011-10-10 14:03:50 +0200133 case ets:lookup(ss7_link_table, {LinksetName, Sls}) of
134 [#slink{user_pid = Pid}] ->
135 % FIXME: check the link state
136 {ok, Pid};
137 _ ->
138 {error, no_such_link}
139 end.
140
141% Resolve linkset name directly connected to given point code
Harald Welte4608ba12011-12-08 12:10:34 +0100142get_linkset_for_dpc(DpcIn) ->
143 Dpc = osmo_util:pointcode2int(DpcIn),
Harald Weltec6e466e2011-10-10 14:03:50 +0200144 Ret = ets:match_object(ss7_linksets,
145 #slinkset{remote_pc = Dpc, _ = '_'}),
146 case Ret of
147 [] ->
148 {error, undefined};
149 [#slinkset{name=Name}|_Tail] ->
150 {ok, Name}
151 end.
152
153% resolve link-handler Pid for given (directly connected) point code/sls
Harald Welte4608ba12011-12-08 12:10:34 +0100154get_pid_for_dpc_sls(DpcIn, Sls) when is_integer(Sls) ->
155 Dpc = osmo_util:pointcode2int(DpcIn),
Harald Weltec6e466e2011-10-10 14:03:50 +0200156 case get_linkset_for_dpc(Dpc) of
157 {error, Err} ->
158 {error, Err};
159 {ok, LinksetName} ->
160 get_pid_for_link(LinksetName, Sls)
161 end.
162
Harald Welte805fac42011-10-12 17:17:55 +0200163% the the local point code for a given linkset
164get_opc_for_linkset(LsName) when is_list(LsName) ->
165 case ets:lookup(ss7_linksets, LsName) of
166 [#slinkset{local_pc = Opc}|_Tail] ->
167 Opc;
168 _ ->
169 undefined
170 end.
171
172% determine if a given point code is local
173is_pc_local(Pc) when is_integer(Pc) ->
174 Ret = ets:match_object(ss7_linksets,
175 #slinkset{local_pc = Pc, _ = '_'}),
176 case Ret of
177 [#slinkset{}] ->
178 true;
179 _ ->
180 false
181 end.
182
Harald Weltec6e466e2011-10-10 14:03:50 +0200183% process a received message on an underlying link
Harald Welte7dadde82011-10-19 13:40:39 +0200184mtp3_rx(Mtp3 = #mtp3_msg{}) ->
185 mtp3_rx(osmo_util:make_prim('MTP', 'TRANSFER',
186 indication, Mtp3));
Harald Weltefe275c02011-12-08 14:19:49 +0100187% FIXME: PAUSE/RESUME/STATUS handling
188mtp3_rx(#primitive{subsystem='MTP', spec_name='PAUSE', gen_name=indication}) ->
189 ok;
190mtp3_rx(#primitive{subsystem='MTP', spec_name='RESUME', gen_name=indication}) ->
191 ok;
192mtp3_rx(#primitive{subsystem='MTP', spec_name='STATUS', gen_name=indication}) ->
193 ok;
Harald Welte7dadde82011-10-19 13:40:39 +0200194mtp3_rx(P = #primitive{parameters=#mtp3_msg{service_ind=Serv}}) ->
Harald Weltec6e466e2011-10-10 14:03:50 +0200195 case ets:lookup(mtp3_services, Serv) of
196 [#service{user_pid = Pid}] ->
Harald Welte7dadde82011-10-19 13:40:39 +0200197 gen_server:cast(Pid, P);
Harald Weltec6e466e2011-10-10 14:03:50 +0200198 _ ->
199 % FIXME: send back some error message on MTP level
200 ok
201 end.
202
203
204% transmit a MTP3 message via any of the avaliable links for the DPC
Harald Welte9b5ea3e2011-12-08 14:09:34 +0100205mtp3_tx(Mtp3 = #mtp3_msg{routing_label = RoutLbl}, Link) ->
206 #mtp3_routing_label{sig_link_sel = Sls} = RoutLbl,
207 % discover the link through which we shall send
208 case get_pid_for_link(Link, Sls) of
209 {error, Error} ->
210 {error, Error};
211 {ok, Pid} ->
212 gen_server:cast(Pid,
213 osmo_util:make_prim('MTP', 'TRANSFER',
214 request, Mtp3))
215 end.
216
217
218% transmit a MTP3 message via any of the avaliable links for the DPC
Harald Weltec6e466e2011-10-10 14:03:50 +0200219mtp3_tx(Mtp3 = #mtp3_msg{routing_label = RoutLbl}) ->
220 #mtp3_routing_label{dest_pc = Dpc, sig_link_sel = Sls} = RoutLbl,
221 % discover the link through which we shall send
222 case get_pid_for_dpc_sls(Dpc, Sls) of
223 {error, Error} ->
224 {error, Error};
225 {ok, Pid} ->
226 gen_server:cast(Pid,
227 osmo_util:make_prim('MTP', 'TRANSFER',
228 request, Mtp3))
229 end.
230
Harald Weltedd57e672011-10-10 14:54:06 +0200231dump() ->
Harald Weltec6e466e2011-10-10 14:03:50 +0200232 List = ets:tab2list(ss7_linksets),
Harald Weltedd57e672011-10-10 14:54:06 +0200233 dump_linksets(List),
Harald Welte0013e792011-10-10 14:58:29 +0200234 SList = ets:tab2list(mtp3_services),
Harald Weltedd57e672011-10-10 14:54:06 +0200235 dump_services(SList).
Harald Weltec6e466e2011-10-10 14:03:50 +0200236
237dump_linksets([]) ->
238 ok;
239dump_linksets([Head|Tail]) when is_record(Head, slinkset) ->
240 dump_single_linkset(Head),
241 dump_linksets(Tail).
242
243dump_single_linkset(Sls) when is_record(Sls, slinkset) ->
244 #slinkset{name = Name, local_pc = Lpc, remote_pc = Rpc,
Harald Weltedd57e672011-10-10 14:54:06 +0200245 user_pid = Pid, state = State} = Sls,
246 io:format("Linkset ~p, Local PC: ~p, Remote PC: ~p, Pid: ~p, State: ~p~n",
247 [Name, Lpc, Rpc, Pid, State]),
Harald Weltec6e466e2011-10-10 14:03:50 +0200248 dump_linkset_links(Name).
249
250dump_linkset_links(Name) ->
251 List = ets:match_object(ss7_link_table,
252 #slink{key={Name,'_'}, _='_'}),
253 dump_links(List).
254
255dump_links([]) ->
256 ok;
257dump_links([Head|Tail]) when is_record(Head, slink) ->
Harald Weltedd57e672011-10-10 14:54:06 +0200258 #slink{name = Name, sls = Sls, state = State, user_pid = Pid} = Head,
259 io:format(" Link ~p, SLS: ~p, Pid: ~p, State: ~p~n",
260 [Name, Sls, Pid, State]),
Harald Weltec6e466e2011-10-10 14:03:50 +0200261 dump_links(Tail).
262
Harald Weltedd57e672011-10-10 14:54:06 +0200263dump_services([]) ->
264 ok;
265dump_services([Head|Tail]) when is_record(Head, service) ->
266 #service{name = Name, user_pid = Pid, service_nr = Nr} = Head,
267 io:format("Service ~p bound to ~p (Pid ~p)~n", [Nr, Name, Pid]),
268 dump_services(Tail).
Harald Weltec6e466e2011-10-10 14:03:50 +0200269
270% server side code
271
272handle_call({register_linkset, {LocalPc, RemotePc, Name}},
273 {FromPid, _FromRef}, S) ->
274 #su_state{linkset_tbl = Tbl} = S,
275 Ls = #slinkset{local_pc = LocalPc, remote_pc = RemotePc,
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200276 name = Name, user_pid = FromPid,
277 state = down, active_sls=[]},
Harald Weltec6e466e2011-10-10 14:03:50 +0200278 case ets:insert_new(Tbl, Ls) of
279 false ->
280 {reply, {error, ets_insert}, S};
281 _ ->
282 % We need to trap the user Pid for EXIT
283 % in order to automatically remove any links/linksets if
284 % the user process dies
285 link(FromPid),
286 {reply, ok, S}
287 end;
288
289handle_call({unregister_linkset, {Name}}, {FromPid, _FromRef}, S) ->
290 #su_state{linkset_tbl = Tbl} = S,
291 ets:delete(Tbl, Name),
292 {reply, ok, S};
293
294handle_call({register_link, {LsName, Sls, Name}},
295 {FromPid, _FromRef}, S) ->
296 #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl} = S,
297 % check if linkset actually exists
298 case ets:lookup(LinksetTbl, LsName) of
299 [#slinkset{}] ->
300 Link = #slink{name = Name, sls = Sls, state = down,
301 user_pid = FromPid, key = {LsName, Sls}},
302 case ets:insert_new(LinkTbl, Link) of
303 false ->
304 {reply, {error, link_exists}, S};
305 _ ->
306 % We need to trap the user Pid for EXIT
307 % in order to automatically remove any links if
308 % the user process dies
309 link(FromPid),
310 {reply, ok, S}
311 end;
312 _ ->
313 {reply, {error, no_such_linkset}, S}
314 end;
315
316handle_call({unregister_link, {LsName, Sls}}, {FromPid, _FromRef}, S) ->
317 #su_state{link_tbl = LinkTbl} = S,
318 ets:delete(LinkTbl, {LsName, Sls}),
319 {reply, ok, S};
320
321handle_call({set_link_state, {LsName, Sls, State}}, {FromPid, _}, S) ->
322 #su_state{link_tbl = LinkTbl} = S,
323 case ets:lookup(LinkTbl, {LsName, Sls}) of
324 [] ->
325 {reply, {error, no_such_link}, S};
326 [Link] ->
327 NewLink = Link#slink{state = State},
328 ets:insert(LinkTbl, NewLink),
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200329 propagate_linkstate_to_linkset(LsName, Sls, State),
Harald Weltec6e466e2011-10-10 14:03:50 +0200330 {reply, ok, S}
331 end;
332
333handle_call({bind_service, {SNum, SName}}, {FromPid, _},
334 #su_state{service_tbl = ServTbl} = S) ->
335 NewServ = #service{name = SName, service_nr = SNum,
336 user_pid = FromPid},
337 case ets:insert_new(ServTbl, NewServ) of
338 false ->
339 {reply, {error, ets_insert}, S};
340 _ ->
Harald Weltedfe15e72011-10-10 14:49:19 +0200341 % We need to trap the user Pid for EXIT
342 % in order to automatically remove any links if
343 % the user process dies
344 link(FromPid),
Harald Weltec6e466e2011-10-10 14:03:50 +0200345 {reply, ok, S}
346 end;
347handle_call({unbind_service, {SNum}}, {FromPid, _},
348 #su_state{service_tbl = ServTbl} = S) ->
349 ets:delete(ServTbl, SNum),
350 {reply, ok, S}.
351
352handle_cast(Info, S) ->
353 error_logger:error_report(["unknown handle_cast",
354 {module, ?MODULE},
355 {info, Info}, {state, S}]),
356 {noreply, S}.
357
358handle_info({'EXIT', Pid, Reason}, S) ->
359 io:format("EXIT from Process ~p (~p), cleaning up tables~n",
360 [Pid, Reason]),
Harald Weltedfe15e72011-10-10 14:49:19 +0200361 #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl,
362 service_tbl = ServiceTbl} = S,
Harald Welte8a9f28c2011-10-10 19:31:27 +0200363 % we decided to keep Linksets as something like global
364 % configuration around and not kill them in case the user who
365 % created them has died.
366 %ets:match_delete(LinksetTbl, #slinkset{user_pid = Pid, _='_'}),
Harald Weltedfe15e72011-10-10 14:49:19 +0200367 ets:match_delete(LinkTbl, #slink{user_pid = Pid, _='_'}),
368 ets:match_delete(ServiceTbl, #service{user_pid = Pid, _='_'}),
Harald Weltec6e466e2011-10-10 14:03:50 +0200369 {noreply, S};
370handle_info(Info, S) ->
371 error_logger:error_report(["unknown handle_info",
372 {module, ?MODULE},
373 {info, Info}, {state, S}]),
374 {noreply, S}.
375
376terminate(Reason, _S) ->
377 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
378 ok.
379
380code_change(_OldVsn, State, _Extra) ->
381 {ok, State}.
Harald Welteb8bfc4e2011-10-11 18:49:59 +0200382
383% update the active_sls state in a linkset after a link state chg
384propagate_linkstate_to_linkset(LsName, Sls, State) ->
385 case ets:lookup(ss7_linksets, LsName) of
386 [Ls = #slinkset{}] ->
387 #slinkset{active_sls = ActSls, remote_pc = Dpc} = Ls,
388 case State of
389 active ->
390 % add Sls to list (unique)
391 ActSls2 = lists:usort([Sls|ActSls]);
392 _ ->
393 % del Sls from list
394 ActSls2 = lists:delete(Sls, ActSls)
395 end,
396 % compute the linkstate state
397 case ActSls2 of
398 [] ->
399 LsState = up_inactive,
400 ss7_routes:delete_route(Dpc, 16#ffff, LsName);
401 _ ->
402 LsState = active,
403 ss7_routes:create_route(Dpc, 16#ffff, LsName)
404 end,
405 ets:insert(ss7_linksets,
406 Ls#slinkset{active_sls = ActSls2,
407 state = LsState});
408 _ ->
409 {error, ets_lookup}
410 end.