VFUK actor: Use new GTT matching code

This allows us to use the osmo_ss7_gtt module for matching Sccp
addresses including GT ranges.

The eunit tests have been extended to test the new code.
This commit is contained in:
Harald Welte 2011-04-06 17:22:30 +02:00
parent a227e76dff
commit 99e92c2426
3 changed files with 63 additions and 11 deletions

View File

@ -21,7 +21,7 @@
-module(mgw_nat_act_bow_onw).
-author("Harald Welte <laforge@gnumonks.org>").
-export([rewrite_actor/5]).
-export([rewrite_actor/5, reload_config/0]).
-include_lib("osmo_ss7/include/sccp.hrl").
@ -53,3 +53,6 @@ rewrite_actor(map, From, _Path, 0, MapDec) ->
% Default action: no rewrite
rewrite_actor(_Level, _From, _Path, _MsgType, Msg) ->
Msg.
reload_config() ->
ok.

View File

@ -21,7 +21,7 @@
-module(mgw_nat_act_vfuk_onw).
-author("Harald Welte <laforge@gnumonks.org>").
-export([rewrite_actor/5]).
-export([rewrite_actor/5, reload_config/0]).
-export([camelph_twalk_cb/3]).
-include_lib("osmo_map/include/map.hrl").
@ -54,17 +54,18 @@ mangle_map_camel_phase(from_msc, Path, MapDec) ->
% Resolve the Global Title of the SCCP Called Addr
{value, #sccp_msg{parameters = SccpPars}} = lists:keysearch(sccp_msg, 1, Path),
CalledAddr = proplists:get_value(called_party_addr, SccpPars),
#global_title{phone_number = PhoneNum} = CalledAddr#sccp_addr.global_title,
PhoneNumInt = osmo_util:digit_list2int(PhoneNum),
{ok, CamelPatchTbl} = application:get_env(mgw_nat, camel_phase_patch_table),
case lists:keysearch(PhoneNumInt, 1, CamelPatchTbl) of
{ok, IntTbl} = application:get_env(mgw_nat, int_camel_ph_tbl),
case osmo_ss7_gtt:global_title_match(IntTbl, CalledAddr) of
false ->
MapDec;
{value, { _Num, PhaseL }} ->
PhaseL ->
#global_title{phone_number = PhoneNum} = CalledAddr#sccp_addr.global_title,
PhoneNumInt = osmo_util:digit_list2int(PhoneNum),
io:format("Rewriting Camel Phase List to ~p, GT ~p~n", [PhaseL, PhoneNumInt]),
osmo_util:tuple_walk(MapDec, fun camelph_twalk_cb/3, [PhaseL])
end.
% tuple tree walker callback function
camelph_twalk_cb(['begin','MapSpecificPDUs_begin',basicROS,invoke,
'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke',
@ -74,3 +75,24 @@ camelph_twalk_cb(['begin','MapSpecificPDUs_begin',basicROS,invoke,
camelph_twalk_cb(_Path, Msg, _Args) ->
% Default case: simply return the unmodified tuple
Msg.
gen_int_camelph_tbl(L) ->
gen_int_camelph_tbl(L, []).
gen_int_camelph_tbl([], Out) ->
Out;
gen_int_camelph_tbl([{GttPart, PhasePart}|Tail], Out) ->
GttMatch = osmo_ss7_gtt:'#new-gtt_match'(GttPart),
% Fixme: use ordered insert!
gen_int_camelph_tbl(Tail, Out ++ [{GttMatch, PhasePart}]).
reload_config() ->
{ok, CamelPatchTblIn} = application:get_env(mgw_nat, camel_phase_patch_table),
io:format("VFUK-ONW actor: reloading config ~p~n", [CamelPatchTblIn]),
try gen_int_camelph_tbl(CamelPatchTblIn) of
TblOut ->
application:set_env(mgw_nat, int_camel_ph_tbl, TblOut)
catch error:Error ->
error_logger:error_report([{error, Error},
{stacktrace, erlang:get_stacktrace()}])
end.

View File

@ -4,6 +4,8 @@
-include_lib("eunit/include/eunit.hrl").
-include_lib("osmo_map/include/map.hrl").
-include_lib("osmo_ss7/include/sccp.hrl").
-include_lib("osmo_ss7/include/osmo_util.hrl").
@ -58,9 +60,13 @@
setup() ->
application:set_env(mgw_nat, camel_phase_patch_table, [
% destination, phase-tuple-list
{ 443859078046778, [phase1] }
]).
% each element in this list is a tuple of two lists:
% first half of the tuple: property-list of #gtt_match field members
% second half: list of atoms for camel phase [ phase1, phase2, phase3 ]
{ [ {gt_range_from, 443850000000000 },
{gt_range_to, 443859999999999 } ], [ phase1 ] }
]),
mgw_nat_act_vfuk_onw:reload_config().
teardown(_) ->
application:unset_env(undefined, camel_phase_patch_table).
@ -73,6 +79,26 @@ camelphase_twalk() ->
fun mgw_nat_act_vfuk_onw:camelph_twalk_cb/3,
[[phase1]])).
build_fake_sccp_msg(CalledDigList) ->
Gt = #global_title{phone_number = CalledDigList},
SccpAddr = #sccp_addr{global_title = Gt},
#sccp_msg{parameters = [{called_party_addr, SccpAddr}]}.
% a full test testing the entire chain...
camelphase_full() ->
% Set up a fake SCCP message with Called Addr and GT
SccpDec = build_fake_sccp_msg([4,4,3,8,5,0,0,0,0,0,0,0,0,0,1]),
% call the rewrite actor
MapOut = mgw_nat_act_vfuk_onw:rewrite_actor(map, from_msc, [SccpDec], 0, ?MAP_DEC_IN),
?assertEqual(?MAP_DEC_OUT, MapOut).
camelphase_full_nomatch() ->
% Set up a fake SCCP message with Called Addr and GT
SccpDec = build_fake_sccp_msg([4,4,3,8,6,5,4,3,2,1,2,3,4,5,1]),
% call the rewrite actor
MapOut = mgw_nat_act_vfuk_onw:rewrite_actor(map, from_msc, [SccpDec], 0, ?MAP_DEC_IN),
?assertEqual(?MAP_DEC_IN, MapOut).
test_pcap(File) ->
Args = [{rewrite_fn, fun mgw_nat_act_vfuk_onw:rewrite_actor/5}],
case file:read_file_info(File) of
@ -89,6 +115,7 @@ camel_phase_test_() ->
fun setup/0,
fun teardown/1,
[ ?_test(camelphase_twalk()),
?_test(camelphase_full()),
?_test(camelphase_full_nomatch()),
{ timeout, 5*60, ?_test(test_pcap("../priv/map.pcap")) } ]
}.