Make MGW nat more flexible by introdicng actors an function references

Instead of a static configuration of rewrite/mangling/patching steps,
we now introduce the concept of a 'rewrite_actor', which is a callback
function that determines which rewrite/patching code to call at which
particular layer of the protocol.

The default rewrite actor "bow_onw" resembles the existing rewrite
behavior.

There is a stub new rewrite actore "vfuk_onw", which will be used
for Camel phase rewriting.
diff --git a/ebin/mgw_nat.app b/ebin/mgw_nat.app
index 705380c..b8babd3 100644
--- a/ebin/mgw_nat.app
+++ b/ebin/mgw_nat.app
@@ -2,11 +2,14 @@
 	[{description, "Media Gateway NAT"},
 	 {vsn, "1"},
 	 {modules, [mgw_nat_app, mgw_nat_sup, mgw_nat_usr, mgw_nat, mgw_nat_test,
-		    sccp_masq, map_masq, sctp_handler]},
+		    sccp_masq, map_masq, sctp_handler,
+		    mgw_nat_act_bow_onw, mgw_nat_act_vfuk_onw]},
 	 {registered, [mgw_nat_app]},
 	 {mod, {mgw_nat_app, []}},
 	 {applications, []},
 	 {env, [
+		{rewrite_actor, bow_onw },
+
 		% SCCP static rewrite rules
 		{sccp_rewrite_tbl, [
 			{ 12340000, 98760000, "HLR" },
@@ -27,6 +30,15 @@
 		{msc_local_port, 2904},
 		{msc_remote_ip, {172,16,1,81}},
 		{stp_remote_ip, {172,16,249,20}},
-		{stp_remote_port, 2904}
+		{stp_remote_port, 2904},
+
+		% MAP rewrite table
+		{map_rewrite_table, [
+			{ msc, 1234500070, 678980004014 },
+			{ hlr, 1234500073, 678980004012 },
+			{ scf, 1234500061, 678980004022 },
+			{ vlr, 1234500071, 678980004013 },
+			{ smsCDA, 678980000105, 678990000465 }
+		]}
 	  ]}
 ]}.
diff --git a/src/mgw_nat.erl b/src/mgw_nat.erl
index d1d2e4c..c60fceb 100644
--- a/src/mgw_nat.erl
+++ b/src/mgw_nat.erl
@@ -20,7 +20,12 @@
 
 -module(mgw_nat).
 -author("Harald Welte <laforge@gnumonks.org>").
--export([mangle_rx_data/3, mangle_rx_data/4]).
+
+% Main entry function for M2UA binary messages
+-export([mangle_rx_data/4]).
+
+% Action functions to apply specific translations
+-export([mangle_rx_sccp/4, mangle_rx_isup/4]).
 
 % exports belwo needed by map_masq.erl
 -export([isup_party_internationalize/2, isup_party_nationalize/2, isup_party_replace_prefix/3]).
@@ -33,17 +38,14 @@
 -include_lib("osmo_ss7/include/isup.hrl").
 -include_lib("osmo_ss7/include/sccp.hrl").
 
-mangle_rx_data(L, From, Data) when is_binary(Data) ->
-	mangle_rx_data(L, From, [], Data).
-
 % mangle the received data
-mangle_rx_data(L, From, Path, Data) when is_list(Path), is_binary(Data) ->
+mangle_rx_data(From, Path, Data, Fn) when is_list(Path), is_binary(Data) ->
 	{ok, M2ua} = m2ua_codec:parse_m2ua_msg(Data),
 	%io:format("M2UA Decode: ~p~n", [M2ua]),
 	case M2ua of
 		#m2ua_msg{msg_class = ?M2UA_MSGC_MAUP,
 			  msg_type = ?M2UA_MAUP_MSGT_DATA} ->
-			M2ua_out = mangle_rx_m2ua_maup(L, From, Path, M2ua);
+			M2ua_out = mangle_rx_m2ua_maup(Fn, From, Path, M2ua);
 		#m2ua_msg{} ->
 			% simply pass it along unmodified
 			M2ua_out = M2ua
@@ -53,11 +55,11 @@
 	m2ua_codec:encode_m2ua_msg(M2ua_out).
 
 % mangle the received M2UA
-mangle_rx_m2ua_maup(L, From, Path, M2ua = #m2ua_msg{parameters = Params}) ->
+mangle_rx_m2ua_maup(Fn, From, Path, M2ua = #m2ua_msg{parameters = Params}) ->
 	{_Len, M2uaPayload} = proplists:get_value(16#300, Params),
 	Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload),
 	%io:format("MTP3 Decode: ~p~n", [Mtp3]),
-	Mtp3_out = mangle_rx_mtp3(L, From, Path ++ [M2ua], Mtp3),
+	Mtp3_out = mangle_rx_mtp3(Fn, From, Path ++ [M2ua], Mtp3),
 	%io:format("MTP3 Encode: ~p~n", [Mtp3_out]),
 	Mtp3OutBin = mtp3_codec:encode_mtp3_msg(Mtp3_out),
 	Params2 = proplists:delete(16#300, Params),
@@ -66,16 +68,16 @@
 	M2ua#m2ua_msg{parameters = ParamsNew}.
 
 % mangle the MTP3 payload
-mangle_rx_mtp3(L, From, Path, Mtp3 = #mtp3_msg{service_ind = Service}) ->
-	mangle_rx_mtp3_serv(L, From, Path, Service, Mtp3).
+mangle_rx_mtp3(Fn, From, Path, Mtp3 = #mtp3_msg{service_ind = Service}) ->
+	mangle_rx_mtp3_serv(Fn, From, Path, Service, Mtp3).
 
 % mangle the ISUP content
-mangle_rx_mtp3_serv(_L, From, Path, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
+mangle_rx_mtp3_serv(Fn, From, Path, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
 	io:format("ISUP In: ~p~n", [Payload]),
 	Isup = isup_codec:parse_isup_msg(Payload),
 	io:format("ISUP Decode: ~p~n", [Isup]),
-	% FIXME
-	IsupMangled = mangle_rx_isup(From, Path, Isup#isup_msg.msg_type, Isup),
+	%IsupMangled = mangle_rx_isup(From, Path, Isup#isup_msg.msg_type, Isup),
+	IsupMangled = Fn(isup, From, Path, Isup#isup_msg.msg_type, Isup),
 	if IsupMangled == Isup ->
 		Mtp3;
 	   true ->
@@ -86,13 +88,15 @@
 		Mtp3#mtp3_msg{payload = Payload_out}
 	end;
 % mangle the SCCP content
-mangle_rx_mtp3_serv(_L, From, Path, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
+mangle_rx_mtp3_serv(Fn, From, Path, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
 	io:format("SCCP In: ~p~n", [Payload]),
 	{ok, Sccp} = sccp_codec:parse_sccp_msg(Payload),
 	io:format("SCCP Decode: ~p~n", [Sccp]),
-	SccpMangled = mangle_rx_sccp(From, Path ++ [Mtp3], Sccp#sccp_msg.msg_type, Sccp),
-	SccpMasqued = sccp_masq:sccp_masq_msg(From, SccpMangled#sccp_msg.msg_type,
-					      SccpMangled),
+	SccpMangled = Fn(sccp, From, Path ++ [Mtp3], Sccp#sccp_msg.msg_type, Sccp),
+	SccpMasqued = mangle_rx_sccp_map(Fn, From, Path ++ [Mtp3], SccpMangled#sccp_msg.msg_type, Sccp),
+	%SccpMangled = mangle_rx_sccp(From, Path ++ [Mtp3], Sccp#sccp_msg.msg_type, Sccp),
+	%SccpMasqued = sccp_masq:sccp_masq_msg(From, SccpMangled#sccp_msg.msg_type,
+	%				      SccpMangled),
 	if SccpMasqued == Sccp ->
 		Mtp3;
 	   true ->
@@ -103,9 +107,22 @@
 		Mtp3#mtp3_msg{payload = Payload_out}
 	end;
 % default: do nothing
-mangle_rx_mtp3_serv(_L, _From, _Path, _, Mtp3) ->
+mangle_rx_mtp3_serv(_Fn, _From, _Path, _, Mtp3) ->
 	Mtp3.
 
+% Mangle the actual MAP payload inside the UDT data portion
+mangle_rx_sccp_map(Fn, From, Path, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
+	UserData = proplists:get_value(user_data, Opts),
+	MapDec = map_codec:parse_tcap_msg(UserData),
+	%MapDecNew = map_masq:mangle_map(From, MapDec),
+	MapDecNew = Fn(map, From, Path ++ [Msg], 0, MapDec),
+	MapEncNew = maybe_re_encode(MapDec, MapDecNew, UserData),
+	Opts3 = lists:keyreplace(user_data, 1, Opts,
+				 {user_data, MapEncNew}),
+	Msg#sccp_msg{parameters = Opts3};
+mangle_rx_sccp_map(_Fn, _From, _Path, _MsgType, Msg) ->
+	Msg.
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 % Actual mangling of the decoded SCCP messages
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -159,8 +176,8 @@
 maybe_re_encode(_DecOrig, DecNew, _MapEncOld) ->
 	map_codec:encode_tcap_msg(DecNew).
 
+% Mangle the SCCP Calling / Called Addresses
 mangle_rx_sccp(From, _Path, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
-	% Mangle the SCCP Calling / Called Addresses
 	CalledParty = proplists:get_value(called_party_addr, Opts),
 	CalledPartyNew = mangle_rx_called(From, CalledParty),
 	CallingParty = proplists:get_value(calling_party_addr, Opts),
@@ -169,14 +186,7 @@
 				 {called_party_addr, CalledPartyNew}),
 	Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
 				 {calling_party_addr, CallingPartyNew}),
-	% Mangle the actual MAP payload inside the UDT data portion
-	UserData = proplists:get_value(user_data, Opts),
-	MapDec = map_codec:parse_tcap_msg(UserData),
-	MapDecNew = map_masq:mangle_map(From, MapDec),
-	MapEncNew = maybe_re_encode(MapDec, MapDecNew, UserData),
-	Opts3 = lists:keyreplace(user_data, 1, Opts2,
-				 {user_data, MapEncNew}),
-	Msg#sccp_msg{parameters = Opts3};
+	Msg#sccp_msg{parameters = Opts2};
 mangle_rx_sccp(_From, _Path, _MsgType, Msg) ->
 	Msg.
 
diff --git a/src/mgw_nat_act_bow_onw.erl b/src/mgw_nat_act_bow_onw.erl
new file mode 100644
index 0000000..25d3734
--- /dev/null
+++ b/src/mgw_nat_act_bow_onw.erl
@@ -0,0 +1,55 @@
+% BOW-ONW specific mgw_nat actor callback functions
+
+% (C) 2011 by Harald Welte <laforge@gnumonks.org>
+% (C) 2011 OnWaves
+%
+% All Rights Reserved
+%
+% This program is free software; you can redistribute it and/or modify
+% it under the terms of the GNU Affero General Public License as
+% published by the Free Software Foundation; either version 3 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 Affero General Public License
+% along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+-module(mgw_nat_act_bow_onw).
+-author("Harald Welte <laforge@gnumonks.org>").
+
+-export([rewrite_actor/5]).
+
+-include_lib("osmo_ss7/include/sccp.hrl").
+
+% Rewrite at SCTP (root) level:
+rewrite_actor(sctp, From, Path, 2, DataBin) ->
+	try mgw_nat:mangle_rx_data(From, Path, DataBin, fun rewrite_actor/5) of
+		Val ->
+			Val
+	catch error:Error ->
+		% some parser error, simply forward msg unmodified
+		io:format("MGW NAT mangling Error: ~p~n", [Error]),
+		DataBin
+	end;
+
+% Rewrite at ISUP level:
+rewrite_actor(isup, From, Path, MsgType, IsupDec) ->
+	mwg_nat:mangle_rx_isup(From, Path, MsgType, IsupDec);
+
+% Rewrite at SCCP level: Static GT rewrite as well as dynamic masquerading
+rewrite_actor(sccp, From, Path, MsgType, SccpDec) ->
+	SccpMangled = mgw_nat:mangle_rx_sccp(From, Path, MsgType, SccpDec),
+	SccpMasqued = sccp_masq:sccp_masq_msg(From, SccpMangled#sccp_msg.msg_type, SccpMangled),
+	SccpMasqued;
+
+% Rewrite at MAP level: call into map_masq module
+rewrite_actor(map, From, _Path, 0, MapDec) ->
+	map_masq:mangle_map(From, MapDec);
+
+% Default action: no rewrite
+rewrite_actor(_Level, _From, _Path, _MsgType, Msg) ->
+	Msg.
diff --git a/src/mgw_nat_act_vfuk_onw.erl b/src/mgw_nat_act_vfuk_onw.erl
new file mode 100644
index 0000000..7c588bc
--- /dev/null
+++ b/src/mgw_nat_act_vfuk_onw.erl
@@ -0,0 +1,47 @@
+% VFUK-ONW specific mgw_nat actor callback functions
+
+% (C) 2011 by Harald Welte <laforge@gnumonks.org>
+% (C) 2011 OnWaves
+%
+% All Rights Reserved
+%
+% This program is free software; you can redistribute it and/or modify
+% it under the terms of the GNU Affero General Public License as
+% published by the Free Software Foundation; either version 3 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 Affero General Public License
+% along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+-module(mgw_nat_act_vfuk_onw).
+-author("Harald Welte <laforge@gnumonks.org>").
+
+-export([rewrite_actor/5]).
+
+% Rewrite at SCTP (root) level:
+rewrite_actor(sctp, From, Path, 2, DataBin) ->
+	try mgw_nat:mangle_rx_data(From, Path, DataBin, fun rewrite_actor/5) of
+		Val ->
+			Val
+	catch error:Error ->
+		% some parser error, simply forward msg unmodified
+		io:format("MGW NAT mangling Error: ~p~n", [Error]),
+		DataBin
+	end;
+
+% Rewrite at MAP level: call into map_masq module
+rewrite_actor(map, From, Path, 0, MapDec) ->
+	mangle_map_camel_phase(From, Path, MapDec);
+
+% Default action: no rewrite
+rewrite_actor(_Level, _From, _Path, _MsgType, Msg) ->
+	Msg.
+
+
+mangle_map_camel_phase(From, Path, MapDec) ->
+	MapDec.
diff --git a/src/mgw_nat_sup.erl b/src/mgw_nat_sup.erl
index 39c41ec..8af7ecd 100644
--- a/src/mgw_nat_sup.erl
+++ b/src/mgw_nat_sup.erl
@@ -27,14 +27,7 @@
 start_link() ->
 	supervisor:start_link({local, ?MODULE}, ?MODULE, []).
 
-init(_Arg) ->
-	{ok, MscLocalIp} = application:get_env(msc_local_ip),
-	{ok, MscLocalPort} = application:get_env(msc_local_port),
-	{ok, MscRemoteIp} = application:get_env(msc_remote_ip),
-	{ok, StpRemoteIp} = application:get_env(stp_remote_ip),
-	{ok, StpRemotePort} = application:get_env(stp_remote_port),
-	SctpHdlrArgs =	[MscLocalIp, MscLocalPort, MscRemoteIp,
-			 StpRemoteIp, StpRemotePort],
-	MgwChild = {mgw_nat_usr, {mgw_nat_usr, start_link, [SctpHdlrArgs]},
+init(Args) ->
+	MgwChild = {mgw_nat_usr, {mgw_nat_usr, start_link, [Args]},
 		    permanent, 2000, worker, [mgw_nat_usr, sctp_handler, mgw_nat]},
 	{ok,{{one_for_all,60,600}, [MgwChild]}}.
diff --git a/src/mgw_nat_test.erl b/src/mgw_nat_test.erl
new file mode 100644
index 0000000..2550f8f
--- /dev/null
+++ b/src/mgw_nat_test.erl
@@ -0,0 +1,77 @@
+% MGW Nat testing code
+
+% (C) 2011 by Harald Welte <laforge@gnumonks.org>
+% (C) 2011 OnWaves
+%
+% All Rights Reserved
+%
+% This program is free software; you can redistribute it and/or modify
+% it under the terms of the GNU Affero General Public License as
+% published by the Free Software Foundation; either version 3 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 Affero General Public License
+% along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+-module(mgw_nat_test).
+-author("Harald Welte <laforge@gnumonks.org>").
+-export([pcap_apply/3]).
+
+-include_lib("epcap/include/epcap_net.hrl").
+
+pcap_apply(File, Filter, Args) ->
+	epcap:start([{file, File}, {filter, Filter}]),
+	loop(Args).
+
+loop(Args) ->
+	receive
+		[{pkthdr, {_,_,_,{datalink,Datalink}}}, {packet, Packet}] ->
+			Decaps = epcap_net:decapsulate_dlt(Datalink, Packet),
+			handle_pkt_cb(Decaps, Args)
+	end,
+	loop(Args).
+
+
+handle_pkt_cb([Ether, IP, Hdr, Payload], Args) ->
+	io:format("~p:~n  ~p/~p~n", [IP, Hdr, Payload]),
+	case Hdr of
+		#sctp{chunks = Chunks} ->
+			handle_sctp_chunks(Chunks, [Ether, IP, Hdr], Args);
+		_ ->
+			ok
+	end.
+
+handle_sctp_chunks([], _Path, _Args) ->
+	ok;
+handle_sctp_chunks([Head|Tail], Path, Args) ->
+	RewriteFn = proplists:get_value(rewrite_fn, Args),
+	case Head of
+		#sctp_chunk{type = 0, payload=#sctp_chunk_data{ppi=2, data=Data}} ->
+			%mgw_nat:mangle_rx_data(l, from_stp, Data, fun handle_rewrite_cb/5);
+			put(rewrite_cb, RewriteFn),
+			shim_rw_actor(sctp, from_stp, Path, 2, Data);
+		_ ->
+			ok
+	end,
+	handle_sctp_chunks(Tail, Path, Args).
+
+% Rewrite at SCTP (root) level:
+shim_rw_actor(sctp, From, Path, 2, DataBin) ->
+	io:format("sctp:~p:~p~n", [From, DataBin]),
+	try mgw_nat:mangle_rx_data(From, Path, DataBin, fun shim_rw_actor/5) of
+		Val ->
+			Val
+	catch error:Error ->
+		% some parser error, simply forward msg unmodified
+		io:format("MGW NAT mangling Error: ~p~n", [Error]),
+		DataBin
+	end;
+shim_rw_actor(Proto, From, Path, MsgType, Msg) ->
+	io:format("~p:~p:~p~n", [Proto, From, Msg]),
+	Fn = get(rewrite_cb),
+	Fn(Proto, From, Path, MsgType, Msg).
diff --git a/src/mgw_nat_usr.erl b/src/mgw_nat_usr.erl
index fb1392a..9dd3d65 100644
--- a/src/mgw_nat_usr.erl
+++ b/src/mgw_nat_usr.erl
@@ -42,10 +42,20 @@
 
 %% Callback functions of the OTP behavior
 
-init(Params) ->
+init(_Params) ->
 	sccp_masq:init(),
 	map_masq:config_update(),
-	apply(sctp_handler, init, Params).
+	{ok, MscLocalIp} = application:get_env(msc_local_ip),
+	{ok, MscLocalPort} = application:get_env(msc_local_port),
+	{ok, MscRemoteIp} = application:get_env(msc_remote_ip),
+	{ok, StpRemoteIp} = application:get_env(stp_remote_ip),
+	{ok, StpRemotePort} = application:get_env(stp_remote_port),
+	{ok, RewriteActor} = application:get_env(rewrite_actor),
+	HandleFn = get_handle_fn(RewriteActor),
+	io:format("Starting mgw_nat_usr with rewrite actor ~p~n", [RewriteActor]),
+	SctpHdlrArgs =	[MscLocalIp, MscLocalPort, MscRemoteIp,
+			 StpRemoteIp, StpRemotePort, HandleFn],
+	apply(sctp_handler, init, SctpHdlrArgs).
 
 handle_cast(stop, LoopData) ->
 	{stop, normal, LoopData};
@@ -65,3 +75,10 @@
 handle_info({sctp, Sock, Ip, Port, Data}, LoopData) ->
 	NewL = sctp_handler:handle_sctp(LoopData, {sctp, Sock, Ip, Port, Data}),
 	{noreply, NewL}.
+
+
+% return rewrite_actor function reference
+get_handle_fn(bow_onw) ->
+	fun mgw_nat_act_bow_onw:rewrite_actor/5;
+get_handle_fn(vfuk_onw) ->
+	fun mgw_nat_act_vfuk_onw:rewrite_actor/5.
diff --git a/src/sctp_handler.erl b/src/sctp_handler.erl
index 333d551..3011cfa 100644
--- a/src/sctp_handler.erl
+++ b/src/sctp_handler.erl
@@ -22,7 +22,7 @@
 
 -module(sctp_handler).
 -author("Harald Welte <laforge@gnumonks.org>").
--export([init/5, handle_sctp/2]).
+-export([init/6, handle_sctp/2]).
 
 -include_lib("kernel/include/inet.hrl").
 -include_lib("kernel/include/inet_sctp.hrl").
@@ -35,13 +35,14 @@
 -record(loop_data,
 	{msc_sock, msc_local_ip, msc_remote_ip, msc_remote_port,
 	 msc_local_port, msc_assoc_id, 
-	 stp_sock, stp_remote_ip, stp_remote_port, stp_assoc_id
+	 stp_sock, stp_remote_ip, stp_remote_port, stp_assoc_id,
+	 handle_fn
 	}).
 
 -define(COMMON_SOCKOPTS, [{active, once}, {reuseaddr, true}]).
 
 % initialize the sockets towards MSC (listening) and STP (connect)
-init(MscLocalIP, MscLocalPort, MscRemoteIP, StpRemoteIP, StpRemotePort) ->
+init(MscLocalIP, MscLocalPort, MscRemoteIP, StpRemoteIP, StpRemotePort, HandleFn) ->
 	{ok, MscSock} = gen_sctp:open([{ip, MscLocalIP},{port,MscLocalPort}]
 					++ ?COMMON_SOCKOPTS),
 	io:format("Listening for MSC on ~w:~w. ~w~n",
@@ -51,7 +52,7 @@
 	L = #loop_data{msc_sock = MscSock, msc_local_ip = MscLocalIP, 
 			msc_remote_ip = MscRemoteIP,
 			stp_sock = StpSock, stp_remote_ip = StpRemoteIP,
-			stp_remote_port = StpRemotePort},
+			stp_remote_port = StpRemotePort, handle_fn = HandleFn},
 	{ok, L}.
 
 % initiate a connection to STP as a client
@@ -61,7 +62,8 @@
 
 % main loop function
 handle_sctp(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port=MscRemotePort,
-		    stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort},
+		    stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort,
+		    handle_fn=HandleFn},
 	    Sctp) ->
 	io:format("Entering receive loop ~p~n", [L]),
 	io:format("======================================================================~n"),
@@ -102,13 +104,13 @@
 		% MSC data
 		{sctp, MscSock, MscRemoteIp, MscRemotePort, {[Anc], Data}} ->
 			io:format("MSC rx data: ~p ~p~n", [Anc, Data]),
-			handle_rx_data(L, from_msc, Anc, Data),
+			handle_rx_data(HandleFn, L, from_msc, Anc, Data),
 			inet:setopts(MscSock, [{active, once}]),
 			NewL = L;
 		% STP data
 		{sctp, StpSock, StpRemoteIp, StpRemotePort, {[Anc], Data}} ->
 			io:format("STP rx data: ~p ~p~n", [Anc, Data]),
-			handle_rx_data(L, from_stp, Anc, Data),
+			handle_rx_data(HandleFn, L, from_stp, Anc, Data),
 			inet:setopts(StpSock, [{active, once}]),
 			NewL = L;
 		{sctp, _Sock, RemoteIp, _Remote_port, {_Anc, Data}}
@@ -124,23 +126,10 @@
 	NewL.
 
 
-try_mangle(L, From, Data) ->
-	try mgw_nat:mangle_rx_data(L, From, Data) of
-		Val ->
-			Val
-		catch error:Error ->
-			% some parser error, simply forward msg unmodified
-			io:format("MGW NAT mangling Error: ~p~n", [Error]),
-			Data
-		end.
-
 % handle incoming data on one of the SCTP sockets
-handle_rx_data(_L, From, SRInfo, Data) when is_binary(Data) ->
-	io:format("Unhandled Rx Data from SCTP from ~p: ~p, ~p~n", [From, SRInfo, Data]);
-
-handle_rx_data(L, From, SRInf = #sctp_sndrcvinfo{ppid = 2, 
+handle_rx_data(Fn, L, From, SRInf = #sctp_sndrcvinfo{ppid = 2,
 						 stream = Stream}, Data) when is_binary(Data) ->
-	DataOut = try_mangle(L, From, Data),
+	DataOut = Fn(sctp, From, [L, SRInf], 2, Data),
 	% send mangled data to other peer
 	case From of
 		from_msc ->
@@ -158,6 +147,7 @@
 	   true ->
 		io:format("Data is NOT equal~n")
 	end,
-	ok = gen_sctp:send(Sock, SndRcvInfo, DataOut).
+	ok = gen_sctp:send(Sock, SndRcvInfo, DataOut);
 
-
+handle_rx_data(_Fn, _L, From, SRInfo, Data) when is_binary(Data) ->
+	io:format("Unhandled Rx Data from SCTP from ~p: ~p, ~p~n", [From, SRInfo, Data]).