blob: 1523611cab88bc06e67308fa2d9b844b9e840e42 [file] [log] [blame]
Harald Welted17e75a2011-01-18 18:25:20 +01001% SCTP Handler for gateway between MSC and STP, transparently
2% rewriting addresses on the fly
3
4% (C) 2011 by Harald Welte <laforge@gnumonks.org>
5% (C) 2011 OnWaves
6%
7% All Rights Reserved
8%
9% This program is free software; you can redistribute it and/or modify
10% it under the terms of the GNU Affero General Public License as
11% published by the Free Software Foundation; either version 3 of the
12% License, or (at your option) any later version.
13%
14% This program is distributed in the hope that it will be useful,
15% but WITHOUT ANY WARRANTY; without even the implied warranty of
16% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17% GNU General Public License for more details.
18%
19% You should have received a copy of the GNU Affero General Public License
20% along with this program. If not, see <http://www.gnu.org/licenses/>.
21
22
23-module(sctp_handler).
24-author("Harald Welte <laforge@gnumonks.org>").
Harald Welteefddf3d2011-01-21 15:16:24 +000025-export([init/5, mangle_rx_data/3]).
Harald Welted17e75a2011-01-18 18:25:20 +010026
27-include_lib("kernel/include/inet.hrl").
28-include_lib("kernel/include/inet_sctp.hrl").
29
30-include("m2ua.hrl").
31-include("mtp3.hrl").
32-include("isup.hrl").
33-include("sccp.hrl").
34
35-record(loop_data,
36 {msc_sock, msc_local_ip, msc_remote_ip, msc_remote_port,
37 msc_local_port, msc_assoc_id,
38 stp_sock, stp_remote_ip, stp_remote_port, stp_assoc_id
39 }).
40
41-define(COMMON_SOCKOPTS, [{active, once}, {reuseaddr, true}]).
42
43% initialize the sockets towards MSC (listening) and STP (connect)
44init(MscLocalIP, MscLocalPort, MscRemoteIP, StpRemoteIP, StpRemotePort) ->
45 {ok, MscSock} = gen_sctp:open([{ip, MscLocalIP},{port,MscLocalPort}]
46 ++ ?COMMON_SOCKOPTS),
47 io:format("Listening for MSC on ~w:~w. ~w~n",
48 [MscLocalIP, MscLocalPort, MscSock]),
49 ok = gen_sctp:listen(MscSock, true),
50 {ok, StpSock} = gen_sctp:open(?COMMON_SOCKOPTS),
51 L = #loop_data{msc_sock = MscSock, msc_local_ip = MscLocalIP,
52 msc_remote_ip = MscRemoteIP,
53 stp_sock = StpSock, stp_remote_ip = StpRemoteIP,
54 stp_remote_port = StpRemotePort},
55 loop(L).
56
57% initiate a connection to STP as a client
58initiate_stp_connection(#loop_data{stp_sock = Sock, stp_remote_ip = IP, stp_remote_port = Port}, Opts) ->
59 io:format("Establishing SCTP conn to STP ~p Port ~p~n", [IP, Port]),
60 gen_sctp:connect(Sock, IP, Port, Opts ++ ?COMMON_SOCKOPTS).
61
62% main loop function
63loop(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port=MscRemotePort,
64 stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort}) ->
65 io:format("Entering receive loop ~p~n", [L]),
66 io:format("======================================================================~n"),
67 receive
68 % MSC connect or disconnect
69 {sctp, MscSock, MscRemoteIp, Port, {ANC, SAC}}
70 when is_record(SAC, sctp_assoc_change) ->
71 io:format("MSC sctp_assoc_change ~p ~p~n", [ANC, SAC]),
72 #sctp_assoc_change{state = SacState, outbound_streams = OutStreams,
73 inbound_streams = InStreams, assoc_id = MscAssocId} = SAC,
74 case SacState of
75 comm_up ->
76 InitMsg = #sctp_initmsg{num_ostreams=InStreams,
77 max_instreams=OutStreams},
78 {ok, StpAssoc} = initiate_stp_connection(L, [{sctp_initmsg,InitMsg}]),
79 io:format("STP Assoc: ~p~n", [StpAssoc]),
80 NewL = L#loop_data{msc_remote_port = Port,
81 msc_assoc_id = MscAssocId,
82 stp_assoc_id = StpAssoc#sctp_assoc_change.assoc_id};
83 comm_lost ->
84 NewL = L,
85 % maybe we should simply die?
Harald Weltebdc7a5c2011-01-21 14:50:15 +000086 io:format("MSC SCTP comm_lost~n"),
Harald Welted17e75a2011-01-18 18:25:20 +010087 foo:bar();
88 addr_unreachable ->
89 NewL = L,
Harald Weltebdc7a5c2011-01-21 14:50:15 +000090 io:format("MSC SCTP addr_unreachable~n"),
Harald Welted17e75a2011-01-18 18:25:20 +010091 % maybe we should simply die?
92 foo:bar()
93 end,
94 inet:setopts(MscSock, [{active, once}]);
95 % STP connect or disconnect
96 {sctp, StpSock, StpRemoteIp, StpRemotePort, {_Anc, SAC}}
97 when is_record(SAC, sctp_assoc_change) ->
98 io:format("STP sctp_assoc_change ~p~n", [SAC]),
99 inet:setopts(StpSock, [{active, once}]),
100 NewL = L;
101 % MSC data
102 {sctp, MscSock, MscRemoteIp, MscRemotePort, {[Anc], Data}} ->
103 io:format("MSC rx data: ~p ~p~n", [Anc, Data]),
104 handle_rx_data(L, from_msc, Anc, Data),
105 inet:setopts(MscSock, [{active, once}]),
106 NewL = L;
107 % STP data
108 {sctp, StpSock, StpRemoteIp, StpRemotePort, {[Anc], Data}} ->
109 io:format("STP rx data: ~p ~p~n", [Anc, Data]),
110 handle_rx_data(L, from_stp, Anc, Data),
111 inet:setopts(StpSock, [{active, once}]),
112 NewL = L;
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000113 {sctp, _Sock, RemoteIp, _Remote_port, {_Anc, Data}}
114 when is_record(Data, sctp_shutdown_event) ->
115 % maybe we should simply die?
116 NewL = L,
117 io:format("SCTP remote ~p shutdown~n", [RemoteIp]),
118 foo:bar();
Harald Welted17e75a2011-01-18 18:25:20 +0100119 Other ->
120 io:format("OTHER ~p~n", [Other]),
121 NewL = L
122 end,
123 loop(NewL).
124
125
126% handle incoming data on one of the SCTP sockets
127handle_rx_data(L, From, SRInf = #sctp_sndrcvinfo{ppid = 2,
128 stream = Stream}, Data) when is_binary(Data) ->
Harald Welteefddf3d2011-01-21 15:16:24 +0000129 DataOut = sctp_handler:mangle_rx_data(L, From, Data),
Harald Welted17e75a2011-01-18 18:25:20 +0100130 % send mangled data to other peer
131 case From of
132 from_msc ->
133 Sock = L#loop_data.stp_sock,
134 AssocId = L#loop_data.stp_assoc_id;
135 from_stp ->
136 Sock = L#loop_data.msc_sock,
137 AssocId = L#loop_data.msc_assoc_id
138 end,
139 SndRcvInfo = #sctp_sndrcvinfo{ppid = 2, stream = Stream, assoc_id = AssocId},
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000140 %io:format("Sending ~p to ~p ~p~n", [DataOut, Sock, SndRcvInfo]),
Harald Welted17e75a2011-01-18 18:25:20 +0100141 % if they are not equal, we will abort here
142 DataOut = Data,
143 io:format("Data is equal~n"),
144 ok = gen_sctp:send(Sock, SndRcvInfo, DataOut).
145
146% mangle the received data
147mangle_rx_data(L, From, Data) when is_binary(Data) ->
148 {ok, M2ua} = m2ua_codec:parse_m2ua_msg(Data),
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000149 %io:format("M2UA Decode: ~p~n", [M2ua]),
Harald Welted17e75a2011-01-18 18:25:20 +0100150 case M2ua of
151 #m2ua_msg{msg_class = ?M2UA_MSGC_MAUP,
152 msg_type = ?M2UA_MAUP_MSGT_DATA} ->
153 M2ua_out = mangle_rx_m2ua_maup(L, From, M2ua);
154 #m2ua_msg{} ->
155 % simply pass it along unmodified
156 M2ua_out = M2ua
157 end,
158 % re-encode the data
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000159 %io:format("M2UA Encode: ~p~n", [M2ua_out]),
Harald Welted17e75a2011-01-18 18:25:20 +0100160 m2ua_codec:encode_m2ua_msg(M2ua_out).
161
162% mangle the received M2UA
163mangle_rx_m2ua_maup(L, From, M2ua = #m2ua_msg{parameters = Params}) ->
164 {_Len, M2uaPayload} = proplists:get_value(16#300, Params),
165 Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload),
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000166 %io:format("MTP3 Decode: ~p~n", [Mtp3]),
Harald Welted17e75a2011-01-18 18:25:20 +0100167 Mtp3_out = mangle_rx_mtp3(L, From, Mtp3),
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000168 %io:format("MTP3 Encode: ~p~n", [Mtp3_out]),
Harald Welted17e75a2011-01-18 18:25:20 +0100169 Mtp3OutBin = mtp3_codec:encode_mtp3_msg(Mtp3_out),
170 Params2 = proplists:delete(16#300, Params),
171 ParamsNew = Params2 ++ [{16#300, {byte_size(Mtp3OutBin), Mtp3OutBin}}],
172 % return mangled parsed m2ua msg
173 M2ua#m2ua_msg{parameters = ParamsNew}.
174
175% mangle the MTP3 payload
176mangle_rx_mtp3(L, From, Mtp3 = #mtp3_msg{service_ind = Service}) ->
177 mangle_rx_mtp3_serv(L, From, Service, Mtp3).
178
179% mangle the ISUP content
180mangle_rx_mtp3_serv(L, From, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000181 io:format("ISUP In: ~p~n", [Payload]),
Harald Welte1dc9e532011-01-21 12:14:11 +0000182 Isup = isup_codec:parse_isup_msg(Payload),
183 io:format("ISUP Decode: ~p~n", [Isup]),
Harald Welted17e75a2011-01-18 18:25:20 +0100184 % FIXME
Harald Welte4c5e10d2011-01-21 16:17:39 +0000185 %mangle_rx_isup(From, Isup#isup_msg.msg_type, Isup),
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000186 case Isup#isup_msg.msg_type of
187 ?ISUP_MSGT_IAM ->
188 io:format("ISUP Encode In: ~p~n", [Isup]),
189 Isup_out = isup_codec:encode_isup_msg(Isup),
190 io:format("ISUP Encode Out: ~p~n", [Isup_out]),
191 % FIXME
Harald Welte4c5e10d2011-01-21 16:17:39 +0000192 if Isup_out == Payload -> ok;
193 true -> io:format("ISUP DATA NOT EQUAL!~n")
194 end,
195 % return modified MTP3 payload
196 Mtp3#mtp3_msg{payload = Isup_out};
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000197 _ ->
Harald Welte4c5e10d2011-01-21 16:17:39 +0000198 % return UNmodified MTP3 payload
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000199 Mtp3
200 end;
Harald Welted17e75a2011-01-18 18:25:20 +0100201% mangle the SCCP content
202mangle_rx_mtp3_serv(L, From, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
203 Sccp = sccp_codec:parse_sccp_msg(Payload),
204 io:format("SCCP Decode: ~p~n", [Sccp]),
205 % FIXME
206 Mtp3;
207% default: do nothing
208mangle_rx_mtp3_serv(_L, _From, _, Mtp3) ->
209 Mtp3.
Harald Welte4c5e10d2011-01-21 16:17:39 +0000210
211-define(MSRN_PFX_MSC, [8,9,0,9,9]).
212-define(MSRN_PFX_STP, [9,2,9,9,4,2,0,0]).
213
214mangle_rx_isup(From, MsgType, Msg = #isup_msg{parameters = Params}) when
215 MsgType == ?ISUP_MSGT_IAM ->
216 CalledNum = proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params),
217 DigitsIn = CalledNum#party_number.phone_number,
218 Last2DigF = lists:sublist(DigitsIn, length(DigitsIn)-2, 3),
219 case From of
220 from_stp ->
221 DigitsOut = ?MSRN_PFX_MSC ++ Last2DigF,
222 io:format("IAM MSRN rewrite (MSC->STP): ~p -> ~p~n",
223 [DigitsIn, DigitsOut]);
224 from_msc ->
225 DigitsOut = DigitsIn,
226 io:format("No support for MSC->STP MSRN rewrite~n")
227 end,
228 CalledNumOut = CalledNum#party_number{phone_number=DigitsOut},
229 ParamsDel = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
230 ParamsOut = [{?ISUP_PAR_CALLED_P_NUM, CalledNumOut}|ParamsDel],
231 #isup_msg{parameters = ParamsOut};
232% default case: no mangling
233mangle_rx_isup(_From, _Type, Msg) when is_record(Msg, isup_msg) ->
234 Msg.