blob: 2dce55c0c5db0d369184cfa37cf565d46e06c70a [file] [log] [blame]
Harald Welte39b19ef2011-03-08 12:38:13 +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 Welte5df83382011-03-08 15:17:32 +010025-export([init/6, handle_sctp/2]).
Harald Welte39b19ef2011-03-08 12:38:13 +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,
Harald Welte5df83382011-03-08 15:17:32 +010038 stp_sock, stp_remote_ip, stp_remote_port, stp_assoc_id,
Harald Weltea227e762011-04-06 01:07:00 +020039 rewrite_act_mod
Harald Welte39b19ef2011-03-08 12:38:13 +010040 }).
41
42-define(COMMON_SOCKOPTS, [{active, once}, {reuseaddr, true}]).
43
44% initialize the sockets towards MSC (listening) and STP (connect)
Harald Weltea227e762011-04-06 01:07:00 +020045init(MscLocalIP, MscLocalPort, MscRemoteIP, StpRemoteIP, StpRemotePort, RewriteActMod) ->
Harald Welte39b19ef2011-03-08 12:38:13 +010046 {ok, MscSock} = gen_sctp:open([{ip, MscLocalIP},{port,MscLocalPort}]
47 ++ ?COMMON_SOCKOPTS),
48 io:format("Listening for MSC on ~w:~w. ~w~n",
49 [MscLocalIP, MscLocalPort, MscSock]),
50 ok = gen_sctp:listen(MscSock, true),
51 {ok, StpSock} = gen_sctp:open(?COMMON_SOCKOPTS),
52 L = #loop_data{msc_sock = MscSock, msc_local_ip = MscLocalIP,
53 msc_remote_ip = MscRemoteIP,
54 stp_sock = StpSock, stp_remote_ip = StpRemoteIP,
Harald Weltea227e762011-04-06 01:07:00 +020055 stp_remote_port = StpRemotePort, rewrite_act_mod = RewriteActMod},
Harald Welte39b19ef2011-03-08 12:38:13 +010056 {ok, L}.
57
58% initiate a connection to STP as a client
59initiate_stp_connection(#loop_data{stp_sock = Sock, stp_remote_ip = IP, stp_remote_port = Port}, Opts) ->
60 io:format("Establishing SCTP conn to STP ~p Port ~p~n", [IP, Port]),
61 gen_sctp:connect(Sock, IP, Port, Opts ++ ?COMMON_SOCKOPTS).
62
63% main loop function
64handle_sctp(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port=MscRemotePort,
Harald Welte5df83382011-03-08 15:17:32 +010065 stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort,
Harald Weltea227e762011-04-06 01:07:00 +020066 rewrite_act_mod=RewriteActMod},
Harald Welte39b19ef2011-03-08 12:38:13 +010067 Sctp) ->
68 io:format("Entering receive loop ~p~n", [L]),
69 io:format("======================================================================~n"),
70 case Sctp of
71 % MSC connect or disconnect
72 {sctp, MscSock, MscRemoteIp, Port, {ANC, SAC}}
73 when is_record(SAC, sctp_assoc_change) ->
74 io:format("MSC sctp_assoc_change ~p ~p~n", [ANC, SAC]),
75 #sctp_assoc_change{state = SacState, outbound_streams = OutStreams,
76 inbound_streams = InStreams, assoc_id = MscAssocId} = SAC,
77 case SacState of
78 comm_up ->
79 InitMsg = #sctp_initmsg{num_ostreams=InStreams,
80 max_instreams=OutStreams},
81 {ok, StpAssoc} = initiate_stp_connection(L, [{sctp_initmsg,InitMsg}]),
82 io:format("STP Assoc: ~p~n", [StpAssoc]),
83 NewL = L#loop_data{msc_remote_port = Port,
84 msc_assoc_id = MscAssocId,
85 stp_assoc_id = StpAssoc#sctp_assoc_change.assoc_id};
86 comm_lost ->
87 NewL = L,
88 % maybe we should simply die?
89 io:format("MSC SCTP comm_lost~n"),
Harald Welte7c406d32011-03-10 09:50:17 +010090 exit(sctp_comm_lost_msc);
Harald Welte39b19ef2011-03-08 12:38:13 +010091 addr_unreachable ->
92 NewL = L,
93 io:format("MSC SCTP addr_unreachable~n"),
94 % maybe we should simply die?
Harald Welte7c406d32011-03-10 09:50:17 +010095 exit(sctp_addr_unreach_msc)
Harald Welte39b19ef2011-03-08 12:38:13 +010096 end,
97 inet:setopts(MscSock, [{active, once}]);
98 % STP connect or disconnect
99 {sctp, StpSock, StpRemoteIp, StpRemotePort, {_Anc, SAC}}
100 when is_record(SAC, sctp_assoc_change) ->
101 io:format("STP sctp_assoc_change ~p~n", [SAC]),
102 inet:setopts(StpSock, [{active, once}]),
103 NewL = L;
104 % MSC data
105 {sctp, MscSock, MscRemoteIp, MscRemotePort, {[Anc], Data}} ->
106 io:format("MSC rx data: ~p ~p~n", [Anc, Data]),
Harald Weltea227e762011-04-06 01:07:00 +0200107 handle_rx_data(RewriteActMod, L, from_msc, Anc, Data),
Harald Welte39b19ef2011-03-08 12:38:13 +0100108 inet:setopts(MscSock, [{active, once}]),
109 NewL = L;
110 % STP data
111 {sctp, StpSock, StpRemoteIp, StpRemotePort, {[Anc], Data}} ->
112 io:format("STP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltea227e762011-04-06 01:07:00 +0200113 handle_rx_data(RewriteActMod, L, from_stp, Anc, Data),
Harald Welte39b19ef2011-03-08 12:38:13 +0100114 inet:setopts(StpSock, [{active, once}]),
115 NewL = L;
116 {sctp, _Sock, RemoteIp, _Remote_port, {_Anc, Data}}
117 when is_record(Data, sctp_shutdown_event) ->
118 % maybe we should simply die?
119 NewL = L,
120 io:format("SCTP remote ~p shutdown~n", [RemoteIp]),
Harald Welte7c406d32011-03-10 09:50:17 +0100121 exit(ctp_remote_shutdown);
Harald Welte39b19ef2011-03-08 12:38:13 +0100122 Other ->
123 io:format("OTHER ~p~n", [Other]),
124 NewL = L
125 end,
126 NewL.
127
128
Harald Welte39b19ef2011-03-08 12:38:13 +0100129% handle incoming data on one of the SCTP sockets
Harald Weltea227e762011-04-06 01:07:00 +0200130handle_rx_data(Mod, L, From, SRInf = #sctp_sndrcvinfo{ppid = 2,
Harald Welte39b19ef2011-03-08 12:38:13 +0100131 stream = Stream}, Data) when is_binary(Data) ->
Harald Weltea227e762011-04-06 01:07:00 +0200132 DataOut = Mod:rewrite_actor(sctp, From, [L, SRInf], 2, Data),
Harald Welte39b19ef2011-03-08 12:38:13 +0100133 % send mangled data to other peer
134 case From of
135 from_msc ->
136 Sock = L#loop_data.stp_sock,
137 AssocId = L#loop_data.stp_assoc_id;
138 from_stp ->
139 Sock = L#loop_data.msc_sock,
140 AssocId = L#loop_data.msc_assoc_id
141 end,
142 SndRcvInfo = #sctp_sndrcvinfo{ppid = 2, stream = Stream, assoc_id = AssocId},
143 %io:format("Sending ~p to ~p ~p~n", [DataOut, Sock, SndRcvInfo]),
144 % if they are not equal, we will abort here
145 if DataOut == Data ->
146 ok;
147 true ->
148 io:format("Data is NOT equal~n")
149 end,
Harald Welte5df83382011-03-08 15:17:32 +0100150 ok = gen_sctp:send(Sock, SndRcvInfo, DataOut);
Harald Welte39b19ef2011-03-08 12:38:13 +0100151
Harald Weltea227e762011-04-06 01:07:00 +0200152handle_rx_data(_Mod, _L, From, SRInfo, Data) when is_binary(Data) ->
Harald Welte5df83382011-03-08 15:17:32 +0100153 io:format("Unhandled Rx Data from SCTP from ~p: ~p, ~p~n", [From, SRInfo, Data]).