erlang
/
osmo-map-masq
Archived
4
0
Fork 0

Initial (untested) version of the full UDP<->patching<->IPA chain

This commit is contained in:
Harald Welte 2010-08-07 13:28:45 +02:00
parent 7d72eb401c
commit 056e05be58
1 changed files with 62 additions and 0 deletions

62
src/osmo_map_masq.erl Normal file
View File

@ -0,0 +1,62 @@
% MAP masquerading application
% (C) 2010 by Harald Welte <laforge@gnumonks.org>
% (C) 2010 by On-Waves
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU General Public License as published by
% the Free Software Foundation; either version 2 of the License, or
% (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU General Public License along
% with this program; if not, write to the Free Software Foundation, Inc.,
% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
-module(osmo_map_masq).
-author('Harald Welte <laforge@gnumonks.org>').
-export([init/4]).
-record(loop_data,
{udpSocket, udpSrvPort, udpRxAddr, udpRxPort,
ipaSocket, ipaStreamID, ipaDstAddr, ipaDstPort}).
init(UdpServerPort, IpaDstAddr, IpaDstPort, IpaStreamID) ->
{ok, UdpSock} = gen_udp:open(UdpServerPort, [binary, inet]),
{ok, TcpSock} = ipa_proto:connect(IpaDstAddr, IpaDstPort, []),
% FIXME: result evaluation
ipa_proto:register_stream(TcpSock, IpaStreamID, self()),
loop(#loop_data{udpSocket=UdpSock, udpSrvPort=UdpServerPort,
ipaSocket=TcpSock, ipaStreamID=IpaStreamID, ipaDstAddr=IpaDstAddr, ipaDstPort=IpaDstPort}).
loop(#loop_data{}=LoopData) ->
io:format("osmo_masq_loop~n"),
receive
{udp, S, ClientIP, ClientPort, Packet} when S =:= LoopData#loop_data.udpSocket ->
io:format("UDP received from ~p:~p ==> ~p~n", [ClientIP, ClientPort, Packet]),
{ok, SccpHdr, SccpPayload} = sccp_proto:split_udt_sync(Packet),
{ok, NewSccpPayload} = tcap_map_patch:handle_tcap_msg(binary_to_list(SccpPayload)),
{ok, NewSccpBinary} = sccp_proto:wrap_udt_sync(SccpHdr, list_to_binary(NewSccpPayload)),
ipa_proto:send(LoopData#loop_data.ipaSocket, LoopData#loop_data.ipaStreamID, NewSccpBinary),
% loop using the (new?) UDP socket Rx IP and Port number
loop(LoopData#loop_data{udpRxAddr=ClientIP, udpRxPort=ClientPort});
{ipa, S, StreamID, Message} when S =:= LoopData#loop_data.ipaSocket,
StreamID =:= LoopData#loop_data.ipaStreamID ->
io:format("IPA received (Stream ~p)~n", [LoopData#loop_data.ipaStreamID]),
{ok, SccpHdr, SccpPayload} = sccp_proto:split_udt_sync(Message),
{ok, NewSccpPayload} = tcap_map_patch:handle_tcap_msg(binary_to_list(SccpPayload)),
{ok, NewSccpBinary} = sccp_proto:wrap_udt_sync(SccpHdr, list_to_binary(NewSccpPayload)),
gen_udp:send(LoopData#loop_data.udpSocket, LoopData#loop_data.udpRxAddr,
LoopData#loop_data.udpRxPort, NewSccpBinary),
loop(LoopData);
{ipa_closed, S} when S =:= LoopData#loop_data.ipaSocket ->
io:format("IPA socket was closed, stopping process~n")
end.