add new mangle_tt_sri_sm module and associated eunit tests

This module is able to match a SCCP message against a given
Destination-GT prefix and checks if the message contains an
Invoke(SRI-for-SM).  If both conditions are true, it alters the TT from
whatever it may currently be to 3.

This is used for SMS special routing cases at the STP.
This commit is contained in:
Harald Welte 2012-05-30 09:38:14 +02:00
parent fb222d9112
commit cb190c278d
2 changed files with 344 additions and 0 deletions

186
src/mangle_tt_sri_sm.erl Normal file
View File

@ -0,0 +1,186 @@
% FIXME
% (C) 2012 by Harald Welte <laforge@gnumonks.org>
% (C) 2012 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/>.
%
% Additional Permission under GNU AGPL version 3 section 7:
%
% If you modify this Program, or any covered work, by linking or
% combining it with runtime libraries of Erlang/OTP as released by
% Ericsson on http://www.erlang.org (or a modified version of these
% libraries), containing parts covered by the terms of the Erlang Public
% License (http://www.erlang.org/EPLICENSE), the licensors of this
% Program grant you additional permission to convey the resulting work
% without the need to license the runtime libraries of Erlang/OTP under
% the GNU Affero General Public License. Corresponding Source for a
% non-source form of such a combination shall include the source code
% for the parts of the runtime libraries of Erlang/OTP used as well as
% that of the covered work.
-module(mangle_tt_sri_sm).
-author("Harald Welte <laforge@gnumonks.org>").
-export([mangle_tt_sri_sm/4]).
-export([gt_match_pfx/2, gt_match_pfx_list/2,
isup_party_match_pfx/2, isup_party_match_pfx_list/2]).
-export([get_tcap_components/1, get_tcap_operation/1, get_tcap_operations/1,
check_for_tcap_op/3, check_for_invoke_sri_sm/1]).
-include_lib("osmo_map/include/map.hrl").
-include_lib("osmo_ss7/include/sccp.hrl").
-include_lib("osmo_ss7/include/isup.hrl").
% high-level function to determine if a Sccp / MAP message contains a Invoke SRI-SM
check_for_invoke_sri_sm(MapDec) ->
check_for_tcap_op(invoke, {local, 45}, MapDec).
% check if there's a prefix match between a given GT and prefix
gt_match_pfx(GT, MatchPfx) when is_record(GT, global_title),
is_integer(MatchPfx) ->
gt_match_pfx(GT, osmo_util:int2digit_list(MatchPfx));
gt_match_pfx(GT, MatchPfx) when is_record(GT, global_title),
is_list(MatchPfx) ->
match_pfx(GT#global_title.phone_number, MatchPfx).
% check if there's a prefix match between a given ISUP party_addr and prefix
isup_party_match_pfx(Party, MatchPfx) when is_record(Party, party_number),
is_integer(MatchPfx) ->
isup_party_match_pfx(Party, osmo_util:int2digit_list(MatchPfx));
isup_party_match_pfx(Party, MatchPfx) when is_record(Party, party_number) ->
DigitsIn = Party#party_number.phone_number,
match_pfx(DigitsIn, MatchPfx).
match_pfx(DigitsIn, MatchPfx) when is_list(DigitsIn), is_list(MatchPfx) ->
MatchPfxLen = length(MatchPfx),
Pfx = lists:sublist(DigitsIn, 1, MatchPfxLen),
case Pfx of
MatchPfx ->
true;
_ ->
false
end.
% check if there's a prefix match of Global Titles among a list of prefixes
gt_match_pfx_list(GT, []) when is_record(GT, global_title) ->
false;
gt_match_pfx_list(GT, [MatchPfx|Tail]) when is_record(GT, global_title) ->
case gt_match_pfx(GT, MatchPfx) of
true ->
true;
_ ->
gt_match_pfx_list(GT, Tail)
end.
% check if there's a prefix match of ISUP Party number among a list of prefixes
isup_party_match_pfx_list(PN, []) when is_record(PN, party_number) ->
false;
isup_party_match_pfx_list(PN, [MatchPfx|Tail]) when is_record(PN, party_number) ->
case isup_party_match_pfx(PN, MatchPfx) of
true ->
true;
_ ->
isup_party_match_pfx_list(PN, Tail)
end.
% get a list of components from the decoded TCAP+MAP nested record
get_tcap_components({'begin', Beg}) ->
get_tcap_components(Beg);
get_tcap_components({'end', Beg}) ->
get_tcap_components(Beg);
get_tcap_components({'continue', Beg}) ->
get_tcap_components(Beg);
% map.erl
get_tcap_components(#'MapSpecificPDUs_begin'{components=Comps}) ->
Comps;
get_tcap_components(#'MapSpecificPDUs_continue'{components=Comps}) ->
Comps;
get_tcap_components(#'MapSpecificPDUs_end'{components=Comps}) ->
Comps;
get_tcap_components(_) ->
[].
% get the MAP operation of a specific component
get_tcap_operation({basicROS, Rec}) ->
get_tcap_operation(Rec);
get_tcap_operation({invoke, Rec}) ->
get_tcap_operation(Rec);
get_tcap_operation({returnResult, Rec}) ->
get_tcap_operation(Rec);
get_tcap_operation({returnResultNotLast, Rec}) ->
get_tcap_operation(Rec);
% map.erl
get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
{invoke, Op};
get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
{invoke, Op};
get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
{invoke, Op};
get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'.opcode};
get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult_result'.opcode};
get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'.opcode};
get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'.opcode};
get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'.opcode};
get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=Res}) ->
{returnResult, Res#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'.opcode}.
% get a list of the MAP operations inside the components of a MAP message
get_tcap_operations(MapDec) ->
Comps = get_tcap_components(MapDec),
[get_tcap_operation(X) || X <- Comps].
check_for_tcap_op(Comp, Op, SccpDec) when is_record(SccpDec, sccp_msg) ->
UserData = proplists:get_value(user_data, SccpDec#sccp_msg.parameters),
MapDec = map_codec:parse_tcap_msg(UserData),
check_for_tcap_op(Comp, Op, MapDec);
check_for_tcap_op(Comp, Op, MapDec) ->
MapOps = get_tcap_operations(MapDec),
% check for invoke of SRI-for-SM:
lists:member({Comp, Op}, MapOps).
mangle_tt_sri_sm(from_msc, _Path, ?SCCP_MSGT_UDT, SccpDec = #sccp_msg{parameters=Opts}) ->
CalledParty = proplists:get_value(called_party_addr, Opts),
CalledGT = CalledParty#sccp_addr.global_title,
{ok, PrefixList} = application:get_env(mgw_nat, mangle_tt_sri_sm_pfx),
case gt_match_pfx_list(CalledGT, PrefixList) of
true ->
case check_for_invoke_sri_sm(SccpDec) of
true ->
CalledGTNew = CalledGT#global_title{trans_type = 3},
CalledPartyNew = CalledParty#sccp_addr{global_title = CalledGTNew},
ParamsOut = lists:keyreplace(called_party_addr, 1, Opts,
{called_party_addr, CalledPartyNew}),
SccpDec#sccp_msg{parameters=ParamsOut};
_ ->
SccpDec
end;
_ ->
SccpDec
end;
mangle_tt_sri_sm(_, _, _, SccpIn) ->
SccpIn.

View File

@ -0,0 +1,158 @@
% Eunit test rig for mangle_tt_sri_sm
-module(mangle_tt_sri_sm_tests).
-author('Harald Welte <laforge@gnumonks.org>').
-include_lib("eunit/include/eunit.hrl").
-include_lib("osmo_map/include/map.hrl").
-include_lib("osmo_ss7/include/isup.hrl").
-include_lib("osmo_ss7/include/sccp.hrl").
-include_lib("osmo_ss7/include/osmo_util.hrl").
-define(SCCP_MAP_INV_SRI_SM,
#sccp_msg{msg_type = 9,
parameters = [{protocol_class, {0,0}},
{called_party_addr, #sccp_addr{res_nat_use = 0,
route_on_ssn = 0,
point_code = undefined,
ssn = 6,
global_title = #global_title{gti = 4,
nature_of_addr_ind = 4,
trans_type = 0,
encoding = undefined,
numbering_plan = 1,
phone_number = [9,1,3,0,0,0,0,0,0,0,1]}}},
{calling_party_addr, #sccp_addr{res_nat_use = 0,
route_on_ssn = 0,
point_code = undefined,
ssn = 8,
global_title = #global_title{gti = 4,
nature_of_addr_ind = 4,
trans_type = 0,
encoding = undefined,
numbering_plan = 1,
phone_number = [9,8,7,0,0,0,0,0,0,1]}}},
{user_data,<<98,70,72,4,81,1,13,65,107,30,40,28,6,7,0,17,134,5,1,1,1,160,17,96,15,128,2,7,128,161,9,6,7,4,0,0,1,0,20,2,108,30,161,28,2,1,64,2,1,45,48,20,128,7,145,114,39,67,83,32,249,129,1,1,130,6,145,83,132,9,0,103>>}]
}).
-define(MAP_INV_SRI_SM, {'begin',
#'MapSpecificPDUs_begin'{
otid = [81,1,2,200],
dialoguePortion = {'EXTERNAL', {syntax,{0,0,17,773,1,1,1}}, asn1_NOVALUE,
[96,15,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3]},
components = [{basicROS,
{invoke, #'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{
invokeId = {present,64},
linkedId = asn1_NOVALUE,
opcode = {local,45},
argument = #'RoutingInfoForSM-Arg'{
msisdn = [145,114,39,67,83,32,249],
'sm-RP-PRI' = true,
serviceCentreAddress = [145,83,132,9,0,103],
_ = asn1_NOVALUE},
_ = asn1_NOVALUE}}}],
_ = asn1_NOVALUE}}).
% helper functions
make_party_number(Digits) when is_integer(Digits) ->
#party_number{phone_number = osmo_util:int2digit_list(Digits)}.
make_gt(Digits) when is_integer(Digits) ->
#global_title{phone_number = osmo_util:int2digit_list(Digits)}.
make_sccp_sri_sm_to(CalledPartyNum) ->
NumL = osmo_util:int2digit_list(CalledPartyNum),
SccpIn = ?SCCP_MAP_INV_SRI_SM,
Called = proplists:get_value(called_party_addr, SccpIn#sccp_msg.parameters),
Dgt = Called#sccp_addr.global_title,
CalledNew = Called#sccp_addr{global_title=Dgt#global_title{phone_number=NumL}},
ParamsOut = lists:keyreplace(called_party_addr, 1, SccpIn#sccp_msg.parameters,
{called_party_addr, CalledNew}),
SccpIn#sccp_msg{parameters=ParamsOut}.
get_dgt_tt(Sccp) when is_record(Sccp, sccp_msg) ->
Called = proplists:get_value(called_party_addr, Sccp#sccp_msg.parameters),
Dgt = Called#sccp_addr.global_title,
Dgt#global_title.trans_type.
% actual test cases
tcap_comps() ->
{'begin', BeginInvoke} = ?MAP_INV_SRI_SM,
Comps = mangle_tt_sri_sm:get_tcap_components(?MAP_INV_SRI_SM),
?assertEqual(BeginInvoke#'MapSpecificPDUs_begin'.components, Comps).
tcap_ops() ->
Ops = mangle_tt_sri_sm:get_tcap_operations(?MAP_INV_SRI_SM),
?assertEqual([{invoke,{local,45}}], Ops).
sri_sm() ->
% test with decoded MAP as well as SCCP input
?assertEqual(true, mangle_tt_sri_sm:check_for_invoke_sri_sm(?MAP_INV_SRI_SM)),
?assertEqual(true, mangle_tt_sri_sm:check_for_invoke_sri_sm(?SCCP_MAP_INV_SRI_SM)).
isup_pfx_match() ->
TrueNum = make_party_number(9101234567),
FalseNum = make_party_number(4901234567),
% test with integer and list input
?assertEqual(true, mangle_tt_sri_sm:isup_party_match_pfx(TrueNum, 91)),
?assertEqual(true, mangle_tt_sri_sm:isup_party_match_pfx(TrueNum, [9,1])),
?assertEqual(false, mangle_tt_sri_sm:isup_party_match_pfx(FalseNum, 91)),
?assertEqual(false, mangle_tt_sri_sm:isup_party_match_pfx(FalseNum, [9,1])).
gt_pfx_match() ->
TrueNum = make_gt(9101234567),
FalseNum = make_gt(4901234567),
% test with integer and list input
?assertEqual(true, mangle_tt_sri_sm:gt_match_pfx(TrueNum, 91)),
?assertEqual(true, mangle_tt_sri_sm:gt_match_pfx(TrueNum, [9,1])),
?assertEqual(false, mangle_tt_sri_sm:gt_match_pfx(FalseNum, 91)),
?assertEqual(false, mangle_tt_sri_sm:gt_match_pfx(FalseNum, [9,1])).
gt_pfx_list_match() ->
TrueNum = make_gt(9101234567),
FalseNum = make_gt(4901234567),
?assertEqual(true, mangle_tt_sri_sm:gt_match_pfx_list(TrueNum, [91, 53])),
?assertEqual(true, mangle_tt_sri_sm:gt_match_pfx_list(TrueNum, [53, 91])),
?assertEqual(false, mangle_tt_sri_sm:gt_match_pfx_list(FalseNum, [91, 53])),
?assertEqual(false, mangle_tt_sri_sm:gt_match_pfx_list(FalseNum, [53, 91])).
tt_mangle() ->
% test the overall macro-function for mangling the TT in case the DGT matches a
% prefix and the message contains an Invoke(SRI-for-SM)
Sccp91 = make_sccp_sri_sm_to(9101234567),
SccpOut91 = mangle_tt_sri_sm:mangle_tt_sri_sm(from_msc, path, ?SCCP_MSGT_UDT, Sccp91),
?assertEqual(3, get_dgt_tt(SccpOut91)),
Sccp43 = make_sccp_sri_sm_to(4301234567),
SccpOut43 = mangle_tt_sri_sm:mangle_tt_sri_sm(from_msc, path, ?SCCP_MSGT_UDT, Sccp91),
?assertEqual(3, get_dgt_tt(SccpOut43)),
Sccp49 = make_sccp_sri_sm_to(4901234567),
SccpOut49 = mangle_tt_sri_sm:mangle_tt_sri_sm(from_msc, path, ?SCCP_MSGT_UDT, Sccp49),
?assertEqual(get_dgt_tt(Sccp49), get_dgt_tt(SccpOut49)).
% setup and teardown
setup() ->
application:set_env(mgw_nat, mangle_tt_sri_sm_pfx, [ 91, 43 ]).
teardown(_) ->
application:unset_env(mgw_nat, mangle_tt_sri_sm_pfx).
mangle_tt_sri_test_() ->
{setup,
fun setup/0,
fun teardown/1,
[
?_test(tcap_comps()),
?_test(tcap_ops()),
?_test(sri_sm()),
?_test(isup_pfx_match()),
?_test(gt_pfx_match()),
?_test(gt_pfx_list_match()),
?_test(tt_mangle())
]
}.