blob: 11c39568d219f885fa39fad65f4d1845defad7d6 [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 Welte789c8b12011-01-22 20:53:50 +000025-export([init/5, handle_sctp/2]).
Harald Welted17e75a2011-01-18 18:25:20 +010026
27-include_lib("kernel/include/inet.hrl").
28-include_lib("kernel/include/inet_sctp.hrl").
29
Harald Welteaca4edc2011-01-21 16:21:12 +000030%-include("m2ua.hrl").
31%-include("mtp3.hrl").
32%-include("isup.hrl").
33%-include("sccp.hrl").
Harald Welted17e75a2011-01-18 18:25:20 +010034
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},
Harald Welte789c8b12011-01-22 20:53:50 +000055 {ok, L}.
Harald Welted17e75a2011-01-18 18:25:20 +010056
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
Harald Welte789c8b12011-01-22 20:53:50 +000063handle_sctp(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 Sctp) ->
Harald Welted17e75a2011-01-18 18:25:20 +010066 io:format("Entering receive loop ~p~n", [L]),
67 io:format("======================================================================~n"),
Harald Welte789c8b12011-01-22 20:53:50 +000068 case Sctp of
Harald Welted17e75a2011-01-18 18:25:20 +010069 % MSC connect or disconnect
70 {sctp, MscSock, MscRemoteIp, Port, {ANC, SAC}}
71 when is_record(SAC, sctp_assoc_change) ->
72 io:format("MSC sctp_assoc_change ~p ~p~n", [ANC, SAC]),
73 #sctp_assoc_change{state = SacState, outbound_streams = OutStreams,
74 inbound_streams = InStreams, assoc_id = MscAssocId} = SAC,
75 case SacState of
76 comm_up ->
77 InitMsg = #sctp_initmsg{num_ostreams=InStreams,
78 max_instreams=OutStreams},
79 {ok, StpAssoc} = initiate_stp_connection(L, [{sctp_initmsg,InitMsg}]),
80 io:format("STP Assoc: ~p~n", [StpAssoc]),
81 NewL = L#loop_data{msc_remote_port = Port,
82 msc_assoc_id = MscAssocId,
83 stp_assoc_id = StpAssoc#sctp_assoc_change.assoc_id};
84 comm_lost ->
85 NewL = L,
86 % maybe we should simply die?
Harald Weltebdc7a5c2011-01-21 14:50:15 +000087 io:format("MSC SCTP comm_lost~n"),
Harald Welte8a848622011-01-21 19:43:27 +000088 exit(1);
Harald Welted17e75a2011-01-18 18:25:20 +010089 addr_unreachable ->
90 NewL = L,
Harald Weltebdc7a5c2011-01-21 14:50:15 +000091 io:format("MSC SCTP addr_unreachable~n"),
Harald Welted17e75a2011-01-18 18:25:20 +010092 % maybe we should simply die?
Harald Welte8a848622011-01-21 19:43:27 +000093 exit(1)
Harald Welted17e75a2011-01-18 18:25:20 +010094 end,
95 inet:setopts(MscSock, [{active, once}]);
96 % STP connect or disconnect
97 {sctp, StpSock, StpRemoteIp, StpRemotePort, {_Anc, SAC}}
98 when is_record(SAC, sctp_assoc_change) ->
99 io:format("STP sctp_assoc_change ~p~n", [SAC]),
100 inet:setopts(StpSock, [{active, once}]),
101 NewL = L;
102 % MSC data
103 {sctp, MscSock, MscRemoteIp, MscRemotePort, {[Anc], Data}} ->
104 io:format("MSC rx data: ~p ~p~n", [Anc, Data]),
105 handle_rx_data(L, from_msc, Anc, Data),
106 inet:setopts(MscSock, [{active, once}]),
107 NewL = L;
108 % STP data
109 {sctp, StpSock, StpRemoteIp, StpRemotePort, {[Anc], Data}} ->
110 io:format("STP rx data: ~p ~p~n", [Anc, Data]),
111 handle_rx_data(L, from_stp, Anc, Data),
112 inet:setopts(StpSock, [{active, once}]),
113 NewL = L;
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000114 {sctp, _Sock, RemoteIp, _Remote_port, {_Anc, Data}}
115 when is_record(Data, sctp_shutdown_event) ->
116 % maybe we should simply die?
117 NewL = L,
118 io:format("SCTP remote ~p shutdown~n", [RemoteIp]),
Harald Welte8a848622011-01-21 19:43:27 +0000119 exit(1);
Harald Welted17e75a2011-01-18 18:25:20 +0100120 Other ->
121 io:format("OTHER ~p~n", [Other]),
122 NewL = L
123 end,
Harald Welte789c8b12011-01-22 20:53:50 +0000124 NewL.
Harald Welted17e75a2011-01-18 18:25:20 +0100125
Harald Welte8a848622011-01-21 19:43:27 +0000126
127try_mangle(L, From, Data) ->
128 try mgw_nat:mangle_rx_data(L, From, Data) of
129 Val ->
130 Val
131 catch error:Error ->
132 % some parser error, simply forward msg unmodified
133 io:format("MGW NAT mangling Error: ~p~n", [Error]),
134 Data
135 end.
136
Harald Welted17e75a2011-01-18 18:25:20 +0100137% handle incoming data on one of the SCTP sockets
138handle_rx_data(L, From, SRInf = #sctp_sndrcvinfo{ppid = 2,
139 stream = Stream}, Data) when is_binary(Data) ->
Harald Welte8a848622011-01-21 19:43:27 +0000140 DataOut = try_mangle(L, From, Data),
Harald Welted17e75a2011-01-18 18:25:20 +0100141 % send mangled data to other peer
142 case From of
143 from_msc ->
144 Sock = L#loop_data.stp_sock,
145 AssocId = L#loop_data.stp_assoc_id;
146 from_stp ->
147 Sock = L#loop_data.msc_sock,
148 AssocId = L#loop_data.msc_assoc_id
149 end,
150 SndRcvInfo = #sctp_sndrcvinfo{ppid = 2, stream = Stream, assoc_id = AssocId},
Harald Weltebdc7a5c2011-01-21 14:50:15 +0000151 %io:format("Sending ~p to ~p ~p~n", [DataOut, Sock, SndRcvInfo]),
Harald Welted17e75a2011-01-18 18:25:20 +0100152 % if they are not equal, we will abort here
Harald Welte646074c2011-01-21 17:09:32 +0000153 if DataOut == Data ->
154 ok;
155 true ->
156 io:format("Data is NOT equal~n")
157 end,
Harald Welted17e75a2011-01-18 18:25:20 +0100158 ok = gen_sctp:send(Sock, SndRcvInfo, DataOut).
159
Harald Welted17e75a2011-01-18 18:25:20 +0100160