blob: 33e452c44befcfb5b0fb65e4e15b5d2427a16528 [file] [log] [blame]
Harald Weltecb190c22012-05-30 09:38:14 +02001% FIXME
2
3% (C) 2012 by Harald Welte <laforge@gnumonks.org>
4% (C) 2012 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% Additional Permission under GNU AGPL version 3 section 7:
22%
23% If you modify this Program, or any covered work, by linking or
24% combining it with runtime libraries of Erlang/OTP as released by
25% Ericsson on http://www.erlang.org (or a modified version of these
26% libraries), containing parts covered by the terms of the Erlang Public
27% License (http://www.erlang.org/EPLICENSE), the licensors of this
28% Program grant you additional permission to convey the resulting work
29% without the need to license the runtime libraries of Erlang/OTP under
30% the GNU Affero General Public License. Corresponding Source for a
31% non-source form of such a combination shall include the source code
32% for the parts of the runtime libraries of Erlang/OTP used as well as
33% that of the covered work.
34
35-module(mangle_tt_sri_sm).
36-author("Harald Welte <laforge@gnumonks.org>").
37
38-export([mangle_tt_sri_sm/4]).
39
40-export([gt_match_pfx/2, gt_match_pfx_list/2,
41 isup_party_match_pfx/2, isup_party_match_pfx_list/2]).
42
43-export([get_tcap_components/1, get_tcap_operation/1, get_tcap_operations/1,
44 check_for_tcap_op/3, check_for_invoke_sri_sm/1]).
45
46-include_lib("osmo_map/include/map.hrl").
47-include_lib("osmo_ss7/include/sccp.hrl").
48-include_lib("osmo_ss7/include/isup.hrl").
49
50% high-level function to determine if a Sccp / MAP message contains a Invoke SRI-SM
51check_for_invoke_sri_sm(MapDec) ->
52 check_for_tcap_op(invoke, {local, 45}, MapDec).
53
54
55% check if there's a prefix match between a given GT and prefix
56gt_match_pfx(GT, MatchPfx) when is_record(GT, global_title),
57 is_integer(MatchPfx) ->
58 gt_match_pfx(GT, osmo_util:int2digit_list(MatchPfx));
59gt_match_pfx(GT, MatchPfx) when is_record(GT, global_title),
60 is_list(MatchPfx) ->
61 match_pfx(GT#global_title.phone_number, MatchPfx).
62
63% check if there's a prefix match between a given ISUP party_addr and prefix
64isup_party_match_pfx(Party, MatchPfx) when is_record(Party, party_number),
65 is_integer(MatchPfx) ->
66 isup_party_match_pfx(Party, osmo_util:int2digit_list(MatchPfx));
67isup_party_match_pfx(Party, MatchPfx) when is_record(Party, party_number) ->
68 DigitsIn = Party#party_number.phone_number,
69 match_pfx(DigitsIn, MatchPfx).
70
71match_pfx(DigitsIn, MatchPfx) when is_list(DigitsIn), is_list(MatchPfx) ->
72 MatchPfxLen = length(MatchPfx),
73 Pfx = lists:sublist(DigitsIn, 1, MatchPfxLen),
74 case Pfx of
75 MatchPfx ->
76 true;
77 _ ->
78 false
79 end.
80
81% check if there's a prefix match of Global Titles among a list of prefixes
82gt_match_pfx_list(GT, []) when is_record(GT, global_title) ->
83 false;
84gt_match_pfx_list(GT, [MatchPfx|Tail]) when is_record(GT, global_title) ->
85 case gt_match_pfx(GT, MatchPfx) of
86 true ->
87 true;
88 _ ->
89 gt_match_pfx_list(GT, Tail)
90 end.
91
92% check if there's a prefix match of ISUP Party number among a list of prefixes
93isup_party_match_pfx_list(PN, []) when is_record(PN, party_number) ->
94 false;
95isup_party_match_pfx_list(PN, [MatchPfx|Tail]) when is_record(PN, party_number) ->
96 case isup_party_match_pfx(PN, MatchPfx) of
97 true ->
98 true;
99 _ ->
100 isup_party_match_pfx_list(PN, Tail)
101 end.
102
103% get a list of components from the decoded TCAP+MAP nested record
104get_tcap_components({'begin', Beg}) ->
105 get_tcap_components(Beg);
106get_tcap_components({'end', Beg}) ->
107 get_tcap_components(Beg);
108get_tcap_components({'continue', Beg}) ->
109 get_tcap_components(Beg);
110% map.erl
111get_tcap_components(#'MapSpecificPDUs_begin'{components=Comps}) ->
112 Comps;
113get_tcap_components(#'MapSpecificPDUs_continue'{components=Comps}) ->
114 Comps;
115get_tcap_components(#'MapSpecificPDUs_end'{components=Comps}) ->
116 Comps;
117get_tcap_components(_) ->
118 [].
119
120% get the MAP operation of a specific component
121get_tcap_operation({basicROS, Rec}) ->
122 get_tcap_operation(Rec);
123get_tcap_operation({invoke, Rec}) ->
124 get_tcap_operation(Rec);
125get_tcap_operation({returnResult, Rec}) ->
126 get_tcap_operation(Rec);
127get_tcap_operation({returnResultNotLast, Rec}) ->
128 get_tcap_operation(Rec);
129% map.erl
130get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
131 {invoke, Op};
132get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
133 {invoke, Op};
134get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{opcode=Op}) ->
135 {invoke, Op};
136get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=Res}) ->
137 {returnResult, Res#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'.opcode};
138get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult'{result=Res}) ->
139 {returnResult, Res#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult_result'.opcode};
Harald Welte6f1f3092012-05-30 13:35:26 +0200140get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=asn1_NOVALUE}) ->
141 % FIXME: check for asn1_NOVALUE in other cases
142 {returnResult, undefined};
Harald Weltecb190c22012-05-30 09:38:14 +0200143get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=Res}) ->
144 {returnResult, Res#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'.opcode};
145get_tcap_operation(#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=Res}) ->
146 {returnResult, Res#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'.opcode};
147get_tcap_operation(#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=Res}) ->
148 {returnResult, Res#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'.opcode};
149get_tcap_operation(#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=Res}) ->
150 {returnResult, Res#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'.opcode}.
151
152% get a list of the MAP operations inside the components of a MAP message
153get_tcap_operations(MapDec) ->
154 Comps = get_tcap_components(MapDec),
155 [get_tcap_operation(X) || X <- Comps].
156
157
158check_for_tcap_op(Comp, Op, SccpDec) when is_record(SccpDec, sccp_msg) ->
159 UserData = proplists:get_value(user_data, SccpDec#sccp_msg.parameters),
160 MapDec = map_codec:parse_tcap_msg(UserData),
161 check_for_tcap_op(Comp, Op, MapDec);
162
163check_for_tcap_op(Comp, Op, MapDec) ->
164 MapOps = get_tcap_operations(MapDec),
165 % check for invoke of SRI-for-SM:
166 lists:member({Comp, Op}, MapOps).
167
168
169mangle_tt_sri_sm(from_msc, _Path, ?SCCP_MSGT_UDT, SccpDec = #sccp_msg{parameters=Opts}) ->
170 CalledParty = proplists:get_value(called_party_addr, Opts),
171 CalledGT = CalledParty#sccp_addr.global_title,
Harald Welte54274d42012-05-30 13:09:58 +0200172 case application:get_env(mgw_nat, mangle_tt_sri_sm_pfx) of
173 {ok, PrefixList} ->
174 case gt_match_pfx_list(CalledGT, PrefixList) of
175 true ->
Harald Weltecb190c22012-05-30 09:38:14 +0200176 case check_for_invoke_sri_sm(SccpDec) of
Harald Welte54274d42012-05-30 13:09:58 +0200177 true ->
178 CalledGTNew = CalledGT#global_title{trans_type = 3},
179 CalledPartyNew = CalledParty#sccp_addr{global_title = CalledGTNew},
180 ParamsOut = lists:keyreplace(called_party_addr, 1, Opts,
181 {called_party_addr, CalledPartyNew}),
182 SccpDec#sccp_msg{parameters=ParamsOut};
183 _ ->
184 SccpDec
Harald Weltecb190c22012-05-30 09:38:14 +0200185 end;
Harald Welte54274d42012-05-30 13:09:58 +0200186 _ ->
Harald Weltecb190c22012-05-30 09:38:14 +0200187 SccpDec
Harald Welte54274d42012-05-30 13:09:58 +0200188 end;
189 _ ->
190 SccpDec
Harald Weltecb190c22012-05-30 09:38:14 +0200191 end;
192mangle_tt_sri_sm(_, _, _, SccpIn) ->
193 SccpIn.