blob: 39c8abe003b68447e03d5bb64f2cea7dcb38697c [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
Harald Welteed01ec42011-01-22 20:54:36 +000067mangle_rx_mtp3_serv(_L, From, ?MTP3_SERV_ISUP, Mtp3 = #mtp3_msg{payload = Payload}) ->
Harald Welteaca4edc2011-01-21 16:21:12 +000068 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
Harald Welte49ec10e2011-01-21 17:21:13 +000072 IsupMangled = mangle_rx_isup(From, Isup#isup_msg.msg_type, Isup),
73 if IsupMangled == Isup ->
74 Mtp3;
75 true ->
76 io:format("ISUP Encode In: ~p~n", [IsupMangled]),
77 Payload_out = isup_codec:encode_isup_msg(IsupMangled),
78 io:format("ISUP Encode Out: ~p~n", [Payload_out]),
79 % return modified MTP3 payload
80 Mtp3#mtp3_msg{payload = Payload_out}
Harald Welteaca4edc2011-01-21 16:21:12 +000081 end;
82% mangle the SCCP content
Harald Welte66517c02011-02-03 14:12:50 +010083mangle_rx_mtp3_serv(_L, From, ?MTP3_SERV_SCCP, Mtp3 = #mtp3_msg{payload = Payload}) ->
84 io:format("SCCP In: ~p~n", [Payload]),
85 {ok, Sccp} = sccp_codec:parse_sccp_msg(Payload),
Harald Welteaca4edc2011-01-21 16:21:12 +000086 io:format("SCCP Decode: ~p~n", [Sccp]),
Harald Welte66517c02011-02-03 14:12:50 +010087 SccpMangled = mangle_rx_sccp(From, Sccp#sccp_msg.msg_type, Sccp),
Harald Welte99f21c62011-02-03 19:05:33 +010088 SccpMasqued = sccp_masq:sccp_masq_msg(From, SccpMangled#sccp_msg.msg_type,
89 SccpMangled),
90 if SccpMasqued == Sccp ->
Harald Welte66517c02011-02-03 14:12:50 +010091 Mtp3;
92 true ->
Harald Welte99f21c62011-02-03 19:05:33 +010093 io:format("SCCP Encode In: ~p~n", [SccpMasqued]),
94 Payload_out = sccp_codec:encode_sccp_msg(SccpMasqued),
Harald Welte66517c02011-02-03 14:12:50 +010095 io:format("SCCP Encode Out: ~p~n", [Payload_out]),
96 % return modified MTP3 payload
97 Mtp3#mtp3_msg{payload = Payload_out}
98 end;
Harald Welteaca4edc2011-01-21 16:21:12 +000099% default: do nothing
100mangle_rx_mtp3_serv(_L, _From, _, Mtp3) ->
101 Mtp3.
102
Harald Welte66517c02011-02-03 14:12:50 +0100103%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
104% Actual mangling of the decoded SCCP messages
105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Harald Welte918c1f22011-02-03 15:55:57 +0100106
Harald Welte93b2ab52011-02-06 21:48:58 +0100107% iterate over list of rewrite tuples and apply translation if there is a match
108do_sccp_gt_rewrite(GT, _From, []) ->
109 GT;
110do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_stp, [Head|List]) ->
111 {MscSide, StpSide, Comment} = Head,
112 if PhoneNum == StpSide ->
113 NewPhoneNum = MscSide,
114 io:format("SCCP STP->MSC rewrite (~p) ~p -> ~p~n",
115 [Comment, PhoneNum, NewPhoneNum]),
116 GT#global_title{phone_number = NewPhoneNum};
117 true ->
118 do_sccp_gt_rewrite(GT, from_stp, List)
Harald Welte918c1f22011-02-03 15:55:57 +0100119 end;
Harald Welte93b2ab52011-02-06 21:48:58 +0100120do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_msc, [Head|List]) ->
121 {MscSide, StpSide, Comment} = Head,
122 if PhoneNum == MscSide ->
123 NewPhoneNum = StpSide,
124 io:format("SCCP MSC->STP rewrite (~p) ~p -> ~p~n",
125 [Comment, PhoneNum, NewPhoneNum]),
126 GT#global_title{phone_number = NewPhoneNum};
127 true ->
128 do_sccp_gt_rewrite(GT, from_msc, List)
129 end.
130
131% mangle called address
132mangle_rx_called(from_stp, Addr = #sccp_addr{global_title = GT}) ->
133 {ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
Harald Welte184f03a2011-02-06 21:58:59 +0100134 GTout = do_sccp_gt_rewrite(GT, from_stp, RewriteTbl),
Harald Welte93b2ab52011-02-06 21:48:58 +0100135 Addr#sccp_addr{global_title = GTout};
Harald Welte918c1f22011-02-03 15:55:57 +0100136mangle_rx_called(_From, Addr) ->
137 Addr.
138
Harald Welte93b2ab52011-02-06 21:48:58 +0100139% mangle calling address
140mangle_rx_calling(from_msc, Addr = #sccp_addr{global_title = GT}) ->
141 {ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
Harald Welte184f03a2011-02-06 21:58:59 +0100142 GTout = do_sccp_gt_rewrite(GT, from_msc, RewriteTbl),
Harald Welte93b2ab52011-02-06 21:48:58 +0100143 Addr#sccp_addr{global_title = GTout};
Harald Welte918c1f22011-02-03 15:55:57 +0100144mangle_rx_calling(_From, Addr) ->
145 Addr.
146
147mangle_rx_sccp(From, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
148 CalledParty = proplists:get_value(called_party_addr, Opts),
149 CalledPartyNew = mangle_rx_called(From, CalledParty),
150 CallingParty = proplists:get_value(calling_party_addr, Opts),
151 CallingPartyNew = mangle_rx_calling(From, CallingParty),
152 Opts1 = lists:keyreplace(called_party_addr, 1, Opts,
153 {called_party_addr, CalledPartyNew}),
154 Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
155 {calling_party_addr, CallingPartyNew}),
156 Msg#sccp_msg{parameters = Opts2};
Harald Welte66517c02011-02-03 14:12:50 +0100157mangle_rx_sccp(_From, _MsgType, Msg) ->
Harald Welte66517c02011-02-03 14:12:50 +0100158 Msg.
Harald Welte49ec10e2011-01-21 17:21:13 +0000159
160%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
161% Actual mangling of the decoded ISUP messages
162%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
163
Harald Welte2fc3e982011-01-21 18:50:36 +0000164% iterate over list of parameters and call mangle_rx_isup_par() for each one
165mangle_rx_isup_params(_From, _MsgType, _Msg, ParListOut, []) ->
166 ParListOut;
167mangle_rx_isup_params(From, MsgType, Msg, ParListOut, [Par|ParList]) ->
168 ParOut = mangle_rx_isup_par(From, MsgType, Msg, Par),
169 mangle_rx_isup_params(From, MsgType, Msg, ParListOut++[ParOut], ParList).
170
171% manipulate phone numbers
Harald Welteed01ec42011-01-22 20:54:36 +0000172mangle_rx_isup_par(From, MsgType, _Msg, {ParType, ParBody}) when
Harald Welte2fc3e982011-01-21 18:50:36 +0000173 ParType == ?ISUP_PAR_CALLED_P_NUM;
Harald Welteed01ec42011-01-22 20:54:36 +0000174 ParType == ?ISUP_PAR_CONNECTED_NUM;
Harald Welte2fc3e982011-01-21 18:50:36 +0000175 ParType == ?ISUP_PAR_CALLING_P_NUM ->
176 NewParBody = mangle_isup_number(From, MsgType, ParType, ParBody),
177 {ParType, NewParBody};
178% defauly case: do not mangle this parameter
179mangle_rx_isup_par(_From, _MsgType, _Msg, Par) ->
180 Par.
181
182% mangle an incoming ISUP message
183mangle_rx_isup(From, MsgType, Msg = #isup_msg{parameters = Params}) ->
184 ParamsOut = mangle_rx_isup_params(From, MsgType, Msg, [], Params),
185 % return message with modified parameter list
186 Msg#isup_msg{parameters = ParamsOut}.
Harald Welte49ec10e2011-01-21 17:21:13 +0000187
Harald Welte62469be2011-01-21 22:47:42 +0100188% STP->MSC: Mangle a Party Number in IAM
Harald Welte49ec10e2011-01-21 17:21:13 +0000189mangle_isup_number(from_stp, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
190 case NumType of
191 ?ISUP_PAR_CALLED_P_NUM ->
Harald Weltef62f0ed2011-01-22 10:13:34 +0100192 % First convert to international number, if it is national
Harald Welte790f3642011-02-03 17:44:50 +0100193 Num1 = isup_party_internationalize(PartyNum,
194 application:get_env(intern_pfx)),
Harald Welte49ec10e2011-01-21 17:21:13 +0000195 io:format("IAM MSRN rewrite (STP->MSC): "),
Harald Welte790f3642011-02-03 17:44:50 +0100196 isup_party_replace_prefix(Num1,
197 application:get_env(msrn_pfx_stp),
198 application:get_env(msrn_pfx_msc));
Harald Welte49ec10e2011-01-21 17:21:13 +0000199 _ ->
200 PartyNum
Harald Welteacb8c2c2011-01-21 17:26:53 +0000201 end;
Harald Welte62469be2011-01-21 22:47:42 +0100202% MSC->STP: Mangle connected number in response to IAM
Harald Welte93443542011-01-21 18:56:58 +0000203mangle_isup_number(from_msc, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CON;
204 MsgT == ?ISUP_MSGT_ANM ->
205 case NumType of
206 ?ISUP_PAR_CONNECTED_NUM ->
207 io:format("CON MSRN rewrite (MSC->STP): "),
Harald Welte790f3642011-02-03 17:44:50 +0100208 Num1 = isup_party_replace_prefix(PartyNum,
209 application:get_env(msrn_pfx_msc),
210 application:get_env(msrn_pfx_stp)),
Harald Weltef62f0ed2011-01-22 10:13:34 +0100211 % Second: convert to national number, if it is international
Harald Welte790f3642011-02-03 17:44:50 +0100212 isup_party_nationalize(Num1,
213 application:get_env(intern_pfx));
Harald Welte93443542011-01-21 18:56:58 +0000214 _ ->
215 PartyNum
216 end;
Harald Welte62469be2011-01-21 22:47:42 +0100217% MAC->STP: Mangle IAM international -> national
Harald Welted25a4542011-01-21 22:42:45 +0100218mangle_isup_number(from_msc, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
219 case NumType of
220 ?ISUP_PAR_CALLED_P_NUM ->
Harald Welte790f3642011-02-03 17:44:50 +0100221 isup_party_nationalize(PartyNum,
222 applicaiton:get_env(intern_pfx));
Harald Welted25a4542011-01-21 22:42:45 +0100223 _ ->
224 PartyNum
225 end;
Harald Welte62469be2011-01-21 22:47:42 +0100226% STP->MSC: Mangle connected number in response to IAM (national->international)
227mangle_isup_number(from_stp, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CON;
228 MsgT == ?ISUP_MSGT_ANM ->
229 case NumType of
230 ?ISUP_PAR_CONNECTED_NUM ->
Harald Welte790f3642011-02-03 17:44:50 +0100231 isup_party_internationalize(PartyNum,
232 application:get_env(intern_pfx));
Harald Welte62469be2011-01-21 22:47:42 +0100233 _ ->
234 PartyNum
235 end;
Harald Welteacb8c2c2011-01-21 17:26:53 +0000236% default case: no rewrite
237mangle_isup_number(from_msc, _, _, PartyNum) ->
238 PartyNum.
Harald Welte49ec10e2011-01-21 17:21:13 +0000239
240% replace the prefix of PartyNum with NewPfx _if_ the current prefix matches MatchPfx
Harald Welte93b2ab52011-02-06 21:48:58 +0100241isup_party_replace_prefix(PartyNum, MatchPfx, NewPfxInt) ->
242 IntIn = PartyNum#party_number.phone_number,
243 DigitsIn = osmo_util:int2digit_list(IntIn),
244 NewPfx = osmo_util:int2digit_list(NewPfxInt),
Harald Welte49ec10e2011-01-21 17:21:13 +0000245 MatchPfxLen = length(MatchPfx),
246 Pfx = lists:sublist(DigitsIn, 1, MatchPfxLen),
247 if Pfx == MatchPfx ->
Harald Welte1df3c552011-01-21 17:33:45 +0000248 Trailer = lists:sublist(DigitsIn, MatchPfxLen+1, length(DigitsIn)-MatchPfxLen),
Harald Welte49ec10e2011-01-21 17:21:13 +0000249 DigitsOut = NewPfx ++ Trailer,
Harald Welte7871c752011-01-21 19:25:23 +0000250 io:format("Prefix rewrite: ~p -> ~p~n", [DigitsIn, DigitsOut]);
Harald Welte49ec10e2011-01-21 17:21:13 +0000251 true ->
Harald Welte7871c752011-01-21 19:25:23 +0000252 io:format("Prefix rewrite: NO MATCH (~p != ~p)~n", [Pfx, MatchPfx]),
Harald Welte49ec10e2011-01-21 17:21:13 +0000253 DigitsOut = DigitsIn
254 end,
Harald Welte93b2ab52011-02-06 21:48:58 +0100255 IntOut = osmo_util:digit_list2int(DigitsOut),
256 PartyNum#party_number{phone_number = IntOut}.
Harald Welte7871c752011-01-21 19:25:23 +0000257
258isup_party_internationalize(PartyNum, CountryCode) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100259 #party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
260 DigitsIn = osmo_util:int2digit_list(IntIn),
Harald Welte7871c752011-01-21 19:25:23 +0000261 case Nature of
262 ?ISUP_ADDR_NAT_NATIONAL ->
263 DigitsOut = CountryCode ++ DigitsIn,
264 NatureOut = ?ISUP_ADDR_NAT_INTERNATIONAL,
265 io:format("Internationalize: ~p -> ~p~n", [DigitsIn, DigitsOut]);
266 _ ->
267 DigitsOut = DigitsIn,
268 NatureOut = Nature
269 end,
Harald Welte93b2ab52011-02-06 21:48:58 +0100270 IntOut = osmo_util:digit_list2int(DigitsOut),
271 PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.
Harald Welted25a4542011-01-21 22:42:45 +0100272
273isup_party_nationalize(PartyNum, CountryCode) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100274 #party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
275 DigitsIn = osmo_util:int2digit_list(IntIn),
Harald Welted25a4542011-01-21 22:42:45 +0100276 CountryCodeLen = length(CountryCode),
277 case Nature of
278 ?ISUP_ADDR_NAT_INTERNATIONAL ->
279 Pfx = lists:sublist(DigitsIn, CountryCodeLen),
280 if Pfx == CountryCode ->
281 DigitsOut = lists:sublist(DigitsIn, CountryCodeLen+1,
282 length(DigitsIn)-CountryCodeLen),
283 NatureOut = ?ISUP_ADDR_NAT_NATIONAL,
284 io:format("Nationalize: ~p -> ~p~n", [DigitsIn, DigitsOut]);
285 true ->
286 DigitsOut = DigitsIn,
287 NatureOut = Nature
288 end;
289 _ ->
290 DigitsOut = DigitsIn,
291 NatureOut = Nature
292 end,
Harald Welte93b2ab52011-02-06 21:48:58 +0100293 IntOut = osmo_util:digit_list2int(DigitsOut),
294 PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.