blob: ff279cc1346d7643de77b607838edd7836a66c21 [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").
24
25% gen_fsm callbacks
26-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
27 terminate/2, code_change/3]).
28
29% our published API
30-export([start_link/0]).
31
32% client functions, may internally talk to our sccp_user server
33-export([register_linkset/3, unregister_linkset/1]).
34-export([register_link/3, unregister_link/2, set_link_state/3]).
35-export([bind_service/2, unbind_service/1]).
36
37-export([get_pid_for_link/2, get_pid_for_dpc_sls/2, mtp3_tx/1,
38 get_linkset_for_dpc/1, dump_all_links/0]).
39
40-record(slink, {
41 key, % {linkset_name, sls}
42 name,
43 linkset_name,
44 sls,
45 user_pid,
46 state
47}).
48
49-record(slinkset, {
50 name,
51 local_pc,
52 remote_pc,
53 user_pid,
54 state,
55 links
56}).
57
58-record(service, {
59 name,
60 service_nr,
61 user_pid
62}).
63
64-record(su_state, {
65 linkset_tbl,
66 link_tbl,
67 service_tbl
68}).
69
70
71% initialization code
72
73start_link() ->
74 gen_server:start_link({local, ?MODULE}, ?MODULE, [], [{debug, [trace]}]).
75
76init(_Arg) ->
77 LinksetTbl = ets:new(ss7_linksets, [ordered_set, named_table,
78 {keypos, #slinkset.name}]),
79 ServiceTbl = ets:new(mtp3_services, [ordered_set, named_table,
80 {keypos, #service.service_nr}]),
81
82 % create a named table so we can query without reference directly
83 % within client/caller process
84 LinkTbl = ets:new(ss7_link_table, [ordered_set, named_table,
85 {keypos, #slink.key}]),
86 {ok, #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl,
87 service_tbl = ServiceTbl}}.
88
89% client side API
90
91% all write operations go through gen_server:call(), as only the ?MODULE
92% process has permission to modify the table content
93
94register_linkset(LocalPc, RemotePc, Name) ->
95 gen_server:call(?MODULE, {register_linkset, {LocalPc, RemotePc, Name}}).
96
97unregister_linkset(Name) ->
98 gen_server:call(?MODULE, {unregister_linkset, {Name}}).
99
100register_link(LinksetName, Sls, Name) ->
101 gen_server:call(?MODULE, {register_link, {LinksetName, Sls, Name}}).
102
103unregister_link(LinksetName, Sls) ->
104 gen_server:call(?MODULE, {unregister_link, {LinksetName, Sls}}).
105
106set_link_state(LinksetName, Sls, State) ->
107 gen_server:call(?MODULE, {set_link_state, {LinksetName, Sls, State}}).
108
109% bind a service (such as ISUP, SCCP) to the MTP3 link manager
110bind_service(ServiceNum, ServiceName) ->
111 gen_server:call(?MODULE, {bind_service, {ServiceNum, ServiceName}}).
112
113% unbind a service (such as ISUP, SCCP) from the MTP3 link manager
114unbind_service(ServiceNum) ->
115 gen_server:call(?MODULE, {unbind_service, {ServiceNum}}).
116
117% the lookup functions can directly use the ets named_table from within
118% the client process, no need to go through a synchronous IPC
119
120get_pid_for_link(LinksetName, Sls) ->
121 case ets:lookup(ss7_link_table, {LinksetName, Sls}) of
122 [#slink{user_pid = Pid}] ->
123 % FIXME: check the link state
124 {ok, Pid};
125 _ ->
126 {error, no_such_link}
127 end.
128
129% Resolve linkset name directly connected to given point code
130get_linkset_for_dpc(Dpc) ->
131 Ret = ets:match_object(ss7_linksets,
132 #slinkset{remote_pc = Dpc, _ = '_'}),
133 case Ret of
134 [] ->
135 {error, undefined};
136 [#slinkset{name=Name}|_Tail] ->
137 {ok, Name}
138 end.
139
140% resolve link-handler Pid for given (directly connected) point code/sls
141get_pid_for_dpc_sls(Dpc, Sls) ->
142 case get_linkset_for_dpc(Dpc) of
143 {error, Err} ->
144 {error, Err};
145 {ok, LinksetName} ->
146 get_pid_for_link(LinksetName, Sls)
147 end.
148
149% process a received message on an underlying link
150mtp3_rx(Mtp3 = #mtp3_msg{service_ind = Serv}) ->
151 case ets:lookup(mtp3_services, Serv) of
152 [#service{user_pid = Pid}] ->
153 gen_server:cast(Pid,
154 osmo_util:make_prim('MTP', 'TRANSFER',
155 indication, Mtp3));
156 _ ->
157 % FIXME: send back some error message on MTP level
158 ok
159 end.
160
161
162% transmit a MTP3 message via any of the avaliable links for the DPC
163mtp3_tx(Mtp3 = #mtp3_msg{routing_label = RoutLbl}) ->
164 #mtp3_routing_label{dest_pc = Dpc, sig_link_sel = Sls} = RoutLbl,
165 % discover the link through which we shall send
166 case get_pid_for_dpc_sls(Dpc, Sls) of
167 {error, Error} ->
168 {error, Error};
169 {ok, Pid} ->
170 gen_server:cast(Pid,
171 osmo_util:make_prim('MTP', 'TRANSFER',
172 request, Mtp3))
173 end.
174
175dump_all_links() ->
176 List = ets:tab2list(ss7_linksets),
177 dump_linksets(List).
178
179dump_linksets([]) ->
180 ok;
181dump_linksets([Head|Tail]) when is_record(Head, slinkset) ->
182 dump_single_linkset(Head),
183 dump_linksets(Tail).
184
185dump_single_linkset(Sls) when is_record(Sls, slinkset) ->
186 #slinkset{name = Name, local_pc = Lpc, remote_pc = Rpc,
187 state = State} = Sls,
188 io:format("Linkset ~p, Local PC: ~p, Remote PC: ~p, State: ~p~n",
189 [Name, Lpc, Rpc, State]),
190 dump_linkset_links(Name).
191
192dump_linkset_links(Name) ->
193 List = ets:match_object(ss7_link_table,
194 #slink{key={Name,'_'}, _='_'}),
195 dump_links(List).
196
197dump_links([]) ->
198 ok;
199dump_links([Head|Tail]) when is_record(Head, slink) ->
200 #slink{name = Name, sls = Sls, state = State} = Head,
201 io:format(" Link ~p, SLS: ~p, State: ~p~n",
202 [Name, Sls, State]),
203 dump_links(Tail).
204
205
206% server side code
207
208handle_call({register_linkset, {LocalPc, RemotePc, Name}},
209 {FromPid, _FromRef}, S) ->
210 #su_state{linkset_tbl = Tbl} = S,
211 Ls = #slinkset{local_pc = LocalPc, remote_pc = RemotePc,
212 name = Name, user_pid = FromPid},
213 case ets:insert_new(Tbl, Ls) of
214 false ->
215 {reply, {error, ets_insert}, S};
216 _ ->
217 % We need to trap the user Pid for EXIT
218 % in order to automatically remove any links/linksets if
219 % the user process dies
220 link(FromPid),
221 {reply, ok, S}
222 end;
223
224handle_call({unregister_linkset, {Name}}, {FromPid, _FromRef}, S) ->
225 #su_state{linkset_tbl = Tbl} = S,
226 ets:delete(Tbl, Name),
227 {reply, ok, S};
228
229handle_call({register_link, {LsName, Sls, Name}},
230 {FromPid, _FromRef}, S) ->
231 #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl} = S,
232 % check if linkset actually exists
233 case ets:lookup(LinksetTbl, LsName) of
234 [#slinkset{}] ->
235 Link = #slink{name = Name, sls = Sls, state = down,
236 user_pid = FromPid, key = {LsName, Sls}},
237 case ets:insert_new(LinkTbl, Link) of
238 false ->
239 {reply, {error, link_exists}, S};
240 _ ->
241 % We need to trap the user Pid for EXIT
242 % in order to automatically remove any links if
243 % the user process dies
244 link(FromPid),
245 {reply, ok, S}
246 end;
247 _ ->
248 {reply, {error, no_such_linkset}, S}
249 end;
250
251handle_call({unregister_link, {LsName, Sls}}, {FromPid, _FromRef}, S) ->
252 #su_state{link_tbl = LinkTbl} = S,
253 ets:delete(LinkTbl, {LsName, Sls}),
254 {reply, ok, S};
255
256handle_call({set_link_state, {LsName, Sls, State}}, {FromPid, _}, S) ->
257 #su_state{link_tbl = LinkTbl} = S,
258 case ets:lookup(LinkTbl, {LsName, Sls}) of
259 [] ->
260 {reply, {error, no_such_link}, S};
261 [Link] ->
262 NewLink = Link#slink{state = State},
263 ets:insert(LinkTbl, NewLink),
264 {reply, ok, S}
265 end;
266
267handle_call({bind_service, {SNum, SName}}, {FromPid, _},
268 #su_state{service_tbl = ServTbl} = S) ->
269 NewServ = #service{name = SName, service_nr = SNum,
270 user_pid = FromPid},
271 case ets:insert_new(ServTbl, NewServ) of
272 false ->
273 {reply, {error, ets_insert}, S};
274 _ ->
Harald Weltedfe15e72011-10-10 14:49:19 +0200275 % We need to trap the user Pid for EXIT
276 % in order to automatically remove any links if
277 % the user process dies
278 link(FromPid),
Harald Weltec6e466e2011-10-10 14:03:50 +0200279 {reply, ok, S}
280 end;
281handle_call({unbind_service, {SNum}}, {FromPid, _},
282 #su_state{service_tbl = ServTbl} = S) ->
283 ets:delete(ServTbl, SNum),
284 {reply, ok, S}.
285
286handle_cast(Info, S) ->
287 error_logger:error_report(["unknown handle_cast",
288 {module, ?MODULE},
289 {info, Info}, {state, S}]),
290 {noreply, S}.
291
292handle_info({'EXIT', Pid, Reason}, S) ->
293 io:format("EXIT from Process ~p (~p), cleaning up tables~n",
294 [Pid, Reason]),
Harald Weltedfe15e72011-10-10 14:49:19 +0200295 #su_state{linkset_tbl = LinksetTbl, link_tbl = LinkTbl,
296 service_tbl = ServiceTbl} = S,
297 ets:match_delete(LinksetTbl, #slinkset{user_pid = Pid, _='_'}),
298 ets:match_delete(LinkTbl, #slink{user_pid = Pid, _='_'}),
299 ets:match_delete(ServiceTbl, #service{user_pid = Pid, _='_'}),
Harald Weltec6e466e2011-10-10 14:03:50 +0200300 {noreply, S};
301handle_info(Info, S) ->
302 error_logger:error_report(["unknown handle_info",
303 {module, ?MODULE},
304 {info, Info}, {state, S}]),
305 {noreply, S}.
306
307terminate(Reason, _S) ->
308 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
309 ok.
310
311code_change(_OldVsn, State, _Extra) ->
312 {ok, State}.