blob: 7d69a0bb3354faf83b4a630c59d428edbfc7c275 [file] [log] [blame]
Harald Welte5cde7622012-01-23 23:18:28 +01001% Osmocom adaptor to interface the IPA core with osmo_ss7
Harald Weltec6e466e2011-10-10 14:03:50 +02002
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/>.
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 Weltec6e466e2011-10-10 14:03:50 +020033
34-module(ss7_link_ipa_client).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behavior(gen_server).
37
38-include_lib("osmo_ss7/include/osmo_util.hrl").
39%-include_lib("osmo_ss7/include/ipa.hrl").
40-include_lib("osmo_ss7/include/sccp.hrl").
41-include_lib("osmo_ss7/include/osmo_ss7.hrl").
Harald Welte5cde7622012-01-23 23:18:28 +010042-include_lib("osmo_ss7/include/mtp3.hrl").
Harald Weltec6e466e2011-10-10 14:03:50 +020043
44-export([start_link/1, init/1]).
45
Harald Welte5cde7622012-01-23 23:18:28 +010046-export([handle_cast/2, handle_info/2]).
Harald Weltec6e466e2011-10-10 14:03:50 +020047
48-record(loop_dat, {
49 ipa_pid,
Harald Welte5cde7622012-01-23 23:18:28 +010050 socket,
Harald Weltec6e466e2011-10-10 14:03:50 +020051 link
52 }).
53
54start_link(Args) ->
55 gen_server:start_link(?MODULE, Args, []).
56
57init(L = #sigtran_link{type = ipa_client, name = Name, linkset_name = LinksetName,
Harald Welte5cde7622012-01-23 23:18:28 +010058 sls = Sls}) ->
59 % start the IPA link to the SG
60 ok = ss7_links:register_link(LinksetName, Sls, Name),
61 {ok, LoopDat2} = reconnect(#loop_dat{link = L}),
62 {ok, LoopDat2}.
63
64handle_info({ipa_closed, {_Sock, _Stream}}, LoopDat) ->
65 set_link_state(LoopDat, down),
66 {ok, LoopDat2} = reconnect(LoopDat),
Harald Welte5208c292012-01-24 00:00:51 +010067 {noreply, LoopDat2}.
Harald Welte5cde7622012-01-23 23:18:28 +010068
69handle_cast(#primitive{subsystem='MTP', gen_name='TRANSFER', spec_name=request,
70 parameters = #mtp3_msg{service_ind = ?MTP3_SERV_SCCP,
71 payload = Data}}, LoopDat) ->
72 #loop_dat{socket = Socket, ipa_pid = Pid} = LoopDat,
73 Pid ! {ipa_send, Socket, 253, Data},
Harald Welte5208c292012-01-24 00:00:51 +010074 {noreply, LoopDat}.
Harald Welte5cde7622012-01-23 23:18:28 +010075
76reconnect(LoopDat = #loop_dat{link=Link}) ->
77 #sigtran_link{local = Local, remote = Remote} = Link,
Harald Welte31da1fd2012-01-28 14:09:59 +010078 #sigtran_peer{ip = LocalIp, port = LocalPort, point_code = LocalPc} = Local,
79 #sigtran_peer{ip = RemoteIp, port = RemotePort, point_code = RemotePc} = Remote,
Harald Welte5cde7622012-01-23 23:18:28 +010080 case ipa_proto:connect(RemoteIp, RemotePort, [], 10000) of
81 {ok, {Socket, IpaPid}} ->
82 set_link_state(LoopDat, up),
Harald Welte31da1fd2012-01-28 14:09:59 +010083 Mtp3Label = #mtp3_routing_label{sig_link_sel=0, origin_pc = RemotePc, dest_pc = LocalPc},
84 ipa_proto:register_stream(Socket, 253, {callback_fn, fun ipa_tx_to_sccp/4, [Mtp3Label]}),
Harald Welte2968ef82012-01-23 23:57:21 +010085 set_link_state(LoopDat, active),
Harald Welte5cde7622012-01-23 23:18:28 +010086 ipa_proto:unblock(Socket),
87 {ok, LoopDat#loop_dat{ipa_pid=IpaPid, socket=Socket}};
88 {error, Reason} ->
89 io:format("Reconnecting TCP (~w)~n", [Reason]),
90 reconnect(LoopDat)
91 end.
Harald Weltec6e466e2011-10-10 14:03:50 +020092
Harald Welte5cde7622012-01-23 23:18:28 +010093set_link_state(#loop_dat{link = #sigtran_link{linkset_name = LinksetName, sls = Sls}}, State) ->
94 ss7_links:set_link_state(LinksetName, Sls, State).
Harald Weltec6e466e2011-10-10 14:03:50 +020095
Harald Welte5cde7622012-01-23 23:18:28 +010096% Callback that we pass to the ipa_proto, which it will call when it wants to
Harald Weltec6e466e2011-10-10 14:03:50 +020097% send a primitive up the stack to SCCP
Harald Welte31da1fd2012-01-28 14:09:59 +010098ipa_tx_to_sccp(_Socket, 253, Data, [Mtp3Label]) ->
99 ss7_links:mtp3_rx(#mtp3_msg{service_ind=?MTP3_SERV_SCCP,
100 routing_label=Mtp3Label, payload=Data}).