blob: 6cdaa8c5a3827a3be9704012760ed3ed68f3e58d [file] [log] [blame]
Harald Welteaca4edc2011-01-21 16:21:12 +00001%
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4% (C) 2011 OnWaves
5%
6% All Rights Reserved
7%
8% This program is free software; you can redistribute it and/or modify
9% it under the terms of the GNU Affero General Public License as
10% published by the Free Software Foundation; either version 3 of the
11% License, or (at your option) any later version.
12%
13% This program is distributed in the hope that it will be useful,
14% but WITHOUT ANY WARRANTY; without even the implied warranty of
15% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16% GNU General Public License for more details.
17%
18% You should have received a copy of the GNU Affero General Public License
19% along with this program. If not, see <http://www.gnu.org/licenses/>.
20
21-module(mgw_nat).
22-author("Harald Welte <laforge@gnumonks.org>").
23-export([mangle_rx_data/3]).
24
25%-include_lib("kernel/include/inet.hrl").
26%-include_lib("kernel/include/inet_sctp.hrl").
27
28-include("m2ua.hrl").
29-include("mtp3.hrl").
30-include("isup.hrl").
31-include("sccp.hrl").
32
33% mangle the received data
34mangle_rx_data(L, From, Data) when is_binary(Data) ->
35 {ok, M2ua} = m2ua_codec:parse_m2ua_msg(Data),
36 %io:format("M2UA Decode: ~p~n", [M2ua]),
37 case M2ua of
38 #m2ua_msg{msg_class = ?M2UA_MSGC_MAUP,
39 msg_type = ?M2UA_MAUP_MSGT_DATA} ->
40 M2ua_out = mangle_rx_m2ua_maup(L, From, M2ua);
41 #m2ua_msg{} ->
42 % simply pass it along unmodified
43 M2ua_out = M2ua
44 end,
45 % re-encode the data
46 %io:format("M2UA Encode: ~p~n", [M2ua_out]),
47 m2ua_codec:encode_m2ua_msg(M2ua_out).
48
49% mangle the received M2UA
50mangle_rx_m2ua_maup(L, From, M2ua = #m2ua_msg{parameters = Params}) ->
51 {_Len, M2uaPayload} = proplists:get_value(16#300, Params),
52 Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload),
53 %io:format("MTP3 Decode: ~p~n", [Mtp3]),
54 Mtp3_out = mangle_rx_mtp3(L, From, Mtp3),
55 %io:format("MTP3 Encode: ~p~n", [Mtp3_out]),
56 Mtp3OutBin = mtp3_codec:encode_mtp3_msg(Mtp3_out),
57 Params2 = proplists:delete(16#300, Params),
58 ParamsNew = Params2 ++ [{16#300, {byte_size(Mtp3OutBin), Mtp3OutBin}}],
59 % return mangled parsed m2ua msg
60 M2ua#m2ua_msg{parameters = ParamsNew}.
61
62% mangle the MTP3 payload
63mangle_rx_mtp3(L, From, Mtp3 = #mtp3_msg{service_ind = Service}) ->
64 mangle_rx_mtp3_serv(L, From, Service, Mtp3).
65
66% mangle the ISUP content
67mangle_rx_mtp3_serv(L, From, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
68 io:format("ISUP In: ~p~n", [Payload]),
69 Isup = isup_codec:parse_isup_msg(Payload),
70 io:format("ISUP Decode: ~p~n", [Isup]),
71 % FIXME
72 %mangle_rx_isup(From, Isup#isup_msg.msg_type, Isup),
73 case Isup#isup_msg.msg_type of
74 ?ISUP_MSGT_IAM ->
75 io:format("ISUP Encode In: ~p~n", [Isup]),
76 Isup_out = isup_codec:encode_isup_msg(Isup),
77 io:format("ISUP Encode Out: ~p~n", [Isup_out]),
78 % FIXME
79 if Isup_out == Payload -> ok;
80 true -> io:format("ISUP DATA NOT EQUAL!~n")
81 end,
82 % return modified MTP3 payload
83 Mtp3#mtp3_msg{payload = Isup_out};
84 _ ->
85 % return UNmodified MTP3 payload
86 Mtp3
87 end;
88% mangle the SCCP content
89mangle_rx_mtp3_serv(L, From, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
90 Sccp = sccp_codec:parse_sccp_msg(Payload),
91 io:format("SCCP Decode: ~p~n", [Sccp]),
92 % FIXME
93 Mtp3;
94% default: do nothing
95mangle_rx_mtp3_serv(_L, _From, _, Mtp3) ->
96 Mtp3.
97
98-define(MSRN_PFX_MSC, [8,9,0,9,9]).
99-define(MSRN_PFX_STP, [9,2,9,9,4,2,0,0]).
100
101mangle_rx_isup(From, MsgType, Msg = #isup_msg{parameters = Params}) when
102 MsgType == ?ISUP_MSGT_IAM ->
103 CalledNum = proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params),
104 DigitsIn = CalledNum#party_number.phone_number,
105 Last2DigF = lists:sublist(DigitsIn, length(DigitsIn)-2, 3),
106 case From of
107 from_stp ->
108 DigitsOut = ?MSRN_PFX_MSC ++ Last2DigF,
109 io:format("IAM MSRN rewrite (MSC->STP): ~p -> ~p~n",
110 [DigitsIn, DigitsOut]);
111 from_msc ->
112 DigitsOut = DigitsIn,
113 io:format("No support for MSC->STP MSRN rewrite~n")
114 end,
115 CalledNumOut = CalledNum#party_number{phone_number=DigitsOut},
116 ParamsDel = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
117 ParamsOut = [{?ISUP_PAR_CALLED_P_NUM, CalledNumOut}|ParamsDel],
118 #isup_msg{parameters = ParamsOut};
119% default case: no mangling
120mangle_rx_isup(_From, _Type, Msg) when is_record(Msg, isup_msg) ->
121 Msg.