[mgw_nat] support an entire list of SCCP mangling rules

Also, use integers for phone numbers instead of lists, as they
are easier for humans to read+write.
This commit is contained in:
Harald Welte 2011-02-06 21:48:58 +01:00
parent 778048918b
commit 93b2ab5255
3 changed files with 60 additions and 39 deletions

View File

@ -5,13 +5,15 @@
{mod, {mgw_nat_app, []}},
{env, [
% SCCP rewrite
{real_hlr_gt, [6,3,9,1,8,0,0,0,4,0,1,2]},
{nat_hlr_gt, [3,5,4,8,9,0,0,0,7,1]},
{sccp_rewrite_tbl, {[
{ 12340000, 98760000, "HLR" },
{ 12340001, 98760001, "VLR" }
]},
% ISUP rewrite
{msrn_pfx_msc, [3,5,4,8,9,0,9,9]},
{msrn_pfx_stp, [6,3,9,2,9,9,4,2,0,0]},
{intern_pfx, [6,3]},
{msrn_pfx_msc, 35489099},
{msrn_pfx_stp, 6392994200]},
{intern_pfx, 63},
% SCTP / IP config
{msc_local_ip, any},

View File

@ -29,10 +29,11 @@ parse_isup_party(<<>>, OddEven, DigitList) ->
% in case of odd number of digits, we need to cut the last
case OddEven of
1 ->
lists:sublist(DigitList, length(DigitList)-1);
L = lists:sublist(DigitList, length(DigitList)-1);
0 ->
DigitList
end;
L = DigitList
end,
osmo_util:digit_list2int(L);
parse_isup_party(BcdBin, OddEven, DigitList) ->
<<Second:4, First:4, Remain/binary>> = BcdBin,
NewDigits = [First, Second],
@ -230,7 +231,8 @@ parse_isup_msg(DataBin) when is_binary(DataBin) ->
% encode a phone number from a list of digits into the BCD binary sequence
encode_isup_party(BcdList) ->
encode_isup_party(BcdInt) ->
BcdList = osmo_util:int2digit_list(BcdInt),
encode_isup_party(BcdList, <<>>, length(BcdList)).
encode_isup_party([], Bin, NumDigits) ->
case NumDigits rem 2 of

View File

@ -104,33 +104,43 @@ mangle_rx_mtp3_serv(_L, _From, _, Mtp3) ->
% Actual mangling of the decoded SCCP messages
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
mangle_rx_called(from_stp, Addr = #sccp_addr{ssn = SSN,
global_title = GT}) ->
{ok, RealHlrGt} = application:get_env(real_hlr_gt),
{ok, NatHlrGt} = application:get_env(nat_hlr_gt),
case {SSN, GT#global_title.phone_number} of
{_, RealHlrGt} ->
GTout = GT#global_title{phone_number = NatHlrGt},
io:format("SCCP STP->MSC rewrite ~p~n", [GTout]),
Addr#sccp_addr{global_title = GTout};
_ ->
Addr
% iterate over list of rewrite tuples and apply translation if there is a match
do_sccp_gt_rewrite(GT, _From, []) ->
GT;
do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_stp, [Head|List]) ->
{MscSide, StpSide, Comment} = Head,
if PhoneNum == StpSide ->
NewPhoneNum = MscSide,
io:format("SCCP STP->MSC rewrite (~p) ~p -> ~p~n",
[Comment, PhoneNum, NewPhoneNum]),
GT#global_title{phone_number = NewPhoneNum};
true ->
do_sccp_gt_rewrite(GT, from_stp, List)
end;
do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_msc, [Head|List]) ->
{MscSide, StpSide, Comment} = Head,
if PhoneNum == MscSide ->
NewPhoneNum = StpSide,
io:format("SCCP MSC->STP rewrite (~p) ~p -> ~p~n",
[Comment, PhoneNum, NewPhoneNum]),
GT#global_title{phone_number = NewPhoneNum};
true ->
do_sccp_gt_rewrite(GT, from_msc, List)
end.
% mangle called address
mangle_rx_called(from_stp, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, 2, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_called(_From, Addr) ->
Addr.
mangle_rx_calling(from_msc, Addr = #sccp_addr{ssn = SSN,
global_title = GT}) ->
{ok, RealHlrGt} = application:get_env(real_hlr_gt),
{ok, NatHlrGt} = application:get_env(nat_hlr_gt),
case {SSN, GT#global_title.phone_number} of
{_, NatHlrGt} ->
GTout = GT#global_title{phone_number = RealHlrGt},
io:format("SCCP MSC->STP rewrite ~p~n", [GTout]),
Addr#sccp_addr{global_title = GTout};
_ ->
Addr
end;
% mangle calling address
mangle_rx_calling(from_msc, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, 1, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_calling(_From, Addr) ->
Addr.
@ -228,8 +238,10 @@ mangle_isup_number(from_msc, _, _, PartyNum) ->
PartyNum.
% replace the prefix of PartyNum with NewPfx _if_ the current prefix matches MatchPfx
isup_party_replace_prefix(PartyNum, MatchPfx, NewPfx) ->
DigitsIn = PartyNum#party_number.phone_number,
isup_party_replace_prefix(PartyNum, MatchPfx, NewPfxInt) ->
IntIn = PartyNum#party_number.phone_number,
DigitsIn = osmo_util:int2digit_list(IntIn),
NewPfx = osmo_util:int2digit_list(NewPfxInt),
MatchPfxLen = length(MatchPfx),
Pfx = lists:sublist(DigitsIn, 1, MatchPfxLen),
if Pfx == MatchPfx ->
@ -240,10 +252,12 @@ isup_party_replace_prefix(PartyNum, MatchPfx, NewPfx) ->
io:format("Prefix rewrite: NO MATCH (~p != ~p)~n", [Pfx, MatchPfx]),
DigitsOut = DigitsIn
end,
PartyNum#party_number{phone_number = DigitsOut}.
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut}.
isup_party_internationalize(PartyNum, CountryCode) ->
#party_number{phone_number = DigitsIn, nature_of_addr_ind = Nature} = PartyNum,
#party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
DigitsIn = osmo_util:int2digit_list(IntIn),
case Nature of
?ISUP_ADDR_NAT_NATIONAL ->
DigitsOut = CountryCode ++ DigitsIn,
@ -253,10 +267,12 @@ isup_party_internationalize(PartyNum, CountryCode) ->
DigitsOut = DigitsIn,
NatureOut = Nature
end,
PartyNum#party_number{phone_number = DigitsOut, nature_of_addr_ind = NatureOut}.
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.
isup_party_nationalize(PartyNum, CountryCode) ->
#party_number{phone_number = DigitsIn, nature_of_addr_ind = Nature} = PartyNum,
#party_number{phone_number = IntIn, nature_of_addr_ind = Nature} = PartyNum,
DigitsIn = osmo_util:int2digit_list(IntIn),
CountryCodeLen = length(CountryCode),
case Nature of
?ISUP_ADDR_NAT_INTERNATIONAL ->
@ -274,4 +290,5 @@ isup_party_nationalize(PartyNum, CountryCode) ->
DigitsOut = DigitsIn,
NatureOut = Nature
end,
PartyNum#party_number{phone_number = DigitsOut, nature_of_addr_ind = NatureOut}.
IntOut = osmo_util:digit_list2int(DigitsOut),
PartyNum#party_number{phone_number = IntOut, nature_of_addr_ind = NatureOut}.