aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHarald Welte <laforge@gnumonks.org>2012-02-13 20:54:17 +0100
committerHarald Welte <laforge@gnumonks.org>2012-02-13 20:54:17 +0100
commit9fe07294ffed6b1c2230becd02643c2b8463e8ac (patch)
treed260a9c5d4f572c471d73df4c6fba3449d8e06c3
parente6d3ea273d7656158c6df2d184c8704b56c58d07 (diff)
mgw_nat: add IMSI matching / prefix-rewrite for SRI-SM
When the MSC responds with a SRI-SM-Response, we match against a user-supplied list of IMSs. If there is a match, we replace the known prefix of the IMSI with a new known prefix.
-rw-r--r--ebin/mgw_nat.app2
-rw-r--r--src/imsi_list.erl79
-rw-r--r--src/map_masq.erl52
-rw-r--r--test/map_masq_tests.erl42
4 files changed, 170 insertions, 5 deletions
diff --git a/ebin/mgw_nat.app b/ebin/mgw_nat.app
index 133addb..0e5366f 100644
--- a/ebin/mgw_nat.app
+++ b/ebin/mgw_nat.app
@@ -3,7 +3,7 @@
{vsn, "1"},
{modules, [mgw_nat_app, mgw_nat_sup, mgw_nat_usr, mgw_nat,
mgw_nat_adm, sccp_masq, map_masq, sctp_handler,
- mgw_nat_act_bow_onw, mgw_nat_act_vfuk_onw]},
+ mgw_nat_act_bow_onw, mgw_nat_act_vfuk_onw, imsi_list]},
{registered, [mgw_nat_app]},
{mod, {mgw_nat_app, []}},
{applications, []},
diff --git a/src/imsi_list.erl b/src/imsi_list.erl
new file mode 100644
index 0000000..2f60673
--- /dev/null
+++ b/src/imsi_list.erl
@@ -0,0 +1,79 @@
+% Maintain a list of IMSIs in a gb_tree and match against it
+
+% (C) 2012 by Harald Welte <laforge@gnumonks.org>
+% (C) 2012 by On-Waves
+%
+% All Rights Reserved
+%
+% This program is free software; you can redistribute it and/or modify
+% it under the terms of the GNU General Public License as published by
+% the Free Software Foundation; either version 2 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 General Public License along
+% with this program; if not, write to the Free Software Foundation, Inc.,
+% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+-module(imsi_list).
+-author('Harald Welte <laforge@gnumonks.org>').
+
+-export([read_file/1, read_list/1, match_imsi/2]).
+
+lines2tree(Iodev) ->
+ lines2tree(Iodev, gb_trees:empty()).
+
+chomp(Line) when is_list(Line) ->
+ case lists:last(Line) of
+ 10 ->
+ lists:sublist(Line, 1, length(Line)-1);
+ _ ->
+ Line
+ end.
+
+lines2tree(Iodev, Tree) ->
+ case file:read_line(Iodev) of
+ eof ->
+ {ok, Tree};
+ {error, Reason} ->
+ {error, Reason};
+ ebadf ->
+ {error, ebadf};
+ {ok, Line} ->
+ % FIXME: convert to digit list
+ Line2 = chomp(Line),
+ Line3 = [case string:to_integer([X]) of {Int,[]} -> Int end || X <- Line2],
+ lines2tree(Iodev, gb_trees:insert(Line3, true, Tree))
+ end.
+
+
+read_file(FileName) ->
+ % read a text file with one IMSI per line into a gb_tree
+ case file:open(FileName, [read]) of
+ {ok, IoDev} ->
+ lines2tree(IoDev);
+ {error, Reason} ->
+ {error, Reason}
+ end.
+
+read_list(List) when is_list(List) ->
+ read_list(List, gb_trees:empty()).
+
+read_list([], Tree) ->
+ Tree;
+read_list([Head|Tail], Tree) ->
+ read_list(Tail, gb_trees:enter(Head, true, Tree)).
+
+match_imsi(Tree, Imsi) when is_list(Imsi) ->
+ case gb_trees:lookup(Imsi, Tree) of
+ {value, true} ->
+ true;
+ {value, _} ->
+ false;
+ none ->
+ false
+ end.
diff --git a/src/map_masq.erl b/src/map_masq.erl
index 87a8028..b3c30e7 100644
--- a/src/map_masq.erl
+++ b/src/map_masq.erl
@@ -1,7 +1,7 @@
% MAP masquerading application
-% (C) 2010-2011 by Harald Welte <laforge@gnumonks.org>
-% (C) 2010-2011 by On-Waves
+% (C) 2010-2012 by Harald Welte <laforge@gnumonks.org>
+% (C) 2010-2012 by On-Waves
%
% All Rights Reserved
%
@@ -123,8 +123,10 @@ patch(From, {routingInfo, RI}) ->
{routingInfo, patch(From, RI)};
% HLR responds to inquiring MSC indicating the current serving MSC number
-patch(From, #'RoutingInfoForSM-Res'{locationInfoWithLMSI = LocInf} = P) ->
- P#'RoutingInfoForSM-Res'{locationInfoWithLMSI = patch(From, LocInf)};
+patch(From, #'RoutingInfoForSM-Res'{locationInfoWithLMSI = LocInf,
+ imsi = Imsi} = P) ->
+ P#'RoutingInfoForSM-Res'{locationInfoWithLMSI = patch(From, LocInf),
+ imsi = patch_imsi(sri_sm_res, From, Imsi)};
patch(From, #'LocationInfoWithLMSI'{'networkNode-Number' = NetNodeNr} = P) ->
NetNodeNrOut = patch_map_isdn_addr(From, NetNodeNr, msc),
P#'LocationInfoWithLMSI'{'networkNode-Number' = NetNodeNrOut};
@@ -456,6 +458,18 @@ config_update() ->
{ok, MapRewriteTbl} = application:get_env(mgw_nat, map_rewrite_table),
MapRewriteTblOut = generate_rewrite_table(MapRewriteTbl),
application:set_env(mgw_nat, map_rewrite_table, MapRewriteTblOut),
+ % (re-)generate IMSI tree from text file
+ case application:get_env(mgw_nat, imsi_rewrite_file) of
+ {ok, ImsiListFile} ->
+ {ok, ImsiTree} = imsi_list:read_file(ImsiListFile),
+ {ok, OldPrefix} = application:get_env(mgw_nat, imsi_rewrite_old_prefix),
+ {ok, NewPrefix} = application:get_env(mgw_nat, imsi_rewrite_new_prefix),
+ io:format("(Re)generated IMSI rewrite table: ~p entries, ~p -> ~p~n",
+ [gb_trees:size(ImsiTree), OldPrefix, NewPrefix]),
+ application:set_env(mgw_nat, imsi_rewrite_tree, {ImsiTree, OldPrefix, NewPrefix});
+ _ ->
+ ok
+ end,
%{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
%{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
%{ok, IntPfx} = application:get_env(intern_pfx),
@@ -479,3 +493,33 @@ generate_rewrite_entry({Name, MscSideInt, StpSideInt}) ->
MscSideList = osmo_util:int2digit_list(MscSideInt),
StpSideList = osmo_util:int2digit_list(StpSideInt),
{Name, MscSideInt, StpSideInt, MscSideList, StpSideList}.
+
+
+% check if we need to rewrite the IMSI
+patch_imsi(sri_sm_res, from_msc, ImsiIn) ->
+ case application:get_env(mgw_nat, imsi_rewrite_tree) of
+ {ok, {ImsiTree, OldPrefix, NewPrefix}} ->
+ % decode IMSI into list of digits
+ Imsi = map_codec:parse_map_addr(ImsiIn),
+ % rewrite prefix, if it matches
+ case imsi_list:match_imsi(ImsiTree, Imsi) of
+ true ->
+ NewImsi = prefix_rewrite(OldPrefix, NewPrefix, Imsi),
+ map_codec:encode_map_tbcd(NewImsi);
+ false ->
+ ImsiIn
+ end;
+ _ ->
+ ImsiIn
+ end;
+patch_imsi(_, _, Imsi) ->
+ Imsi.
+
+prefix_rewrite(OldPrefix, NewPrefix, Imsi) when is_list(OldPrefix), is_list(NewPrefix), is_list(Imsi) ->
+ case lists:sublist(Imsi, length(OldPrefix)) of
+ OldPrefix ->
+ % remove old prefix and prepend new prefix
+ NewPrefix ++ lists:sublist(Imsi, length(OldPrefix)+1, length(Imsi));
+ _ ->
+ Imsi
+ end.
diff --git a/test/map_masq_tests.erl b/test/map_masq_tests.erl
new file mode 100644
index 0000000..1f37d97
--- /dev/null
+++ b/test/map_masq_tests.erl
@@ -0,0 +1,42 @@
+-module(map_masq_tests).
+
+-include_lib("eunit/include/eunit.hrl").
+-include_lib("osmo_map/include/map.hrl").
+
+-define(OLD_PFX, [2,6,2,7,7]).
+-define(NEW_PFX, [9,0,1,7,7]).
+
+-define(IMSI_TRUE, [0,0,0,0,0,0,0,0,0,9]).
+-define(IMSI_FALSE, [1,0,0,0,0,0,0,0,0,1]).
+-define(SRI_SM_MATCH_IN, gen_sri_sm(?OLD_PFX ++ ?IMSI_TRUE)).
+-define(SRI_SM_MATCH_OUT, gen_sri_sm(?NEW_PFX ++ ?IMSI_TRUE)).
+-define(SRI_SM_NOMATCH_IN, gen_sri_sm(?OLD_PFX ++ ?IMSI_FALSE)).
+
+gen_sri_sm(Imsi) when is_list(Imsi) ->
+ {'begin', #'MapSpecificPDUs_begin'{otid=[0,0,0,1], components=[{basicROS, {returnResult, #'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{invokeId = 1, result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{opcode={local, 2342}, result=#'RoutingInfoForSM-Res'{imsi=map_codec:encode_map_tbcd(Imsi), _ = asn1_NOVALUE}, _ = asn1_NOVALUE}, _ = asn1_NOVALUE}}}], _ = asn1_NOVALUE}}.
+
+
+setup() ->
+ Tree = imsi_list:read_list([?OLD_PFX ++ ?IMSI_TRUE]),
+ application:set_env(mgw_nat, imsi_rewrite_tree, {Tree, ?OLD_PFX, ?NEW_PFX}).
+
+teardown(_) ->
+ application:unset_env(mgw_nat, imsi_rewrite_tree).
+
+sri_sm_match() ->
+ ?assertEqual(?SRI_SM_MATCH_OUT, map_masq:mangle_map(from_msc, ?SRI_SM_MATCH_IN)).
+
+sri_sm_nomatch() ->
+ ?assertEqual(?SRI_SM_NOMATCH_IN, map_masq:mangle_map(from_msc, ?SRI_SM_NOMATCH_IN)).
+
+sri_sm_stp_msc() ->
+ ?assertEqual(?SRI_SM_MATCH_IN, map_masq:mangle_map(from_stp, ?SRI_SM_MATCH_IN)).
+
+map_masq_test_() ->
+ {setup,
+ fun setup/0,
+ fun teardown/1,
+ [ ?_test(sri_sm_match()),
+ ?_test(sri_sm_nomatch()),
+ ?_test(sri_sm_stp_msc()) ]
+ }.