blob: f3039ebdcccf8db909a83c767f4e1cacab500515 [file] [log] [blame]
Harald Welte1f47f672011-04-02 14:33:31 +02001% Osmocom Global Title Translation
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
Harald Welte1f47f672011-04-02 14:33:31 +020033
34-module(osmo_ss7_gtt).
35-author('Harald Welte <laforge@gnumonks.org>').
36
37-include("sccp.hrl").
38-include("gtt.hrl").
39
40-export([global_title_match/2, apply_gtt_actions/2, execute_gtt/2]).
41
Harald Welte8e7cdaf2011-04-02 17:24:47 +020042-compile({parse_transform, exprecs}).
43-export_records([gtt_match, gtt_act_repl_digits, gtt_act_repl_num_plan]).
44
Harald Welte1f47f672011-04-02 14:33:31 +020045% Match a given GT against an ordered list of {match, action} tuples
Harald Welte24a49242011-04-02 17:58:04 +020046global_title_match([], _Gt) ->
Harald Welte1f47f672011-04-02 14:33:31 +020047 false;
48global_title_match([{Match, Action}|Tail], Gt) when is_record(Gt, global_title) ->
49 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
50 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
Harald Welte6e508b62011-04-16 14:11:05 +020051 % in an ordered list, we can assume that no trailing rules will
52 % match
Harald Welte1f47f672011-04-02 14:33:31 +020053 false;
54 true ->
55 case single_gt_match(Match, Gt) of
56 true ->
57 Action;
58 _ ->
59 % iterate further over the list of GTT rules
60 global_title_match(Tail, Gt)
61 end
Harald Welte24a49242011-04-02 17:58:04 +020062 end;
63% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +020064global_title_match([{Match, Action}|Tail], SccpAddr) when
65 is_record(SccpAddr, sccp_addr) ->
Harald Welte24a49242011-04-02 17:58:04 +020066 Gt = SccpAddr#sccp_addr.global_title,
67 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
68 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
Harald Welte6e508b62011-04-16 14:11:05 +020069 % in an ordered list, we can assume that no trailing rules will
70 % match
Harald Welte24a49242011-04-02 17:58:04 +020071 false;
72 true ->
73 case single_gt_match(Match, SccpAddr) of
74 true ->
75 Action;
76 _ ->
77 % iterate further over the list of GTT rules
78 global_title_match(Tail, SccpAddr)
79 end
Harald Welte1f47f672011-04-02 14:33:31 +020080 end.
81
Harald Welte24a49242011-04-02 17:58:04 +020082
Harald Welte1f47f672011-04-02 14:33:31 +020083% perform matching of a given global title against a single match
Harald Welte6e508b62011-04-16 14:11:05 +020084single_gt_match(Match, Gt) when is_record(Match, gtt_match),
85 is_record(Gt, global_title) ->
Harald Welte1f47f672011-04-02 14:33:31 +020086 #gtt_match{gt_range_from = RangeFrom, gt_range_to = RangeTo,
Harald Welte6e508b62011-04-16 14:11:05 +020087 numbering_plan = NumPlan,
88 nature_of_addr_ind = NatureInd} = Match,
89 #global_title{phone_number = GtPhoneNum,
90 numbering_plan = GtNumPlan,
91 nature_of_addr_ind = GtNature} = Gt,
Harald Welte1f47f672011-04-02 14:33:31 +020092 % build a list of the individual criteria that all have to match
Harald Welte6e508b62011-04-16 14:11:05 +020093 SubMatchList = [{digits, {RangeFrom, RangeTo}, GtPhoneNum},
94 {numbering_plan, NumPlan, GtNumPlan},
95 {nature_of_addr_ind, NatureInd, GtNature}],
Harald Welte24a49242011-04-02 17:58:04 +020096 gt_sub_match_list(SubMatchList);
97% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +020098single_gt_match(Match, SccpAddr) when is_record(Match, gtt_match),
99 is_record(SccpAddr, sccp_addr) ->
Harald Welte24a49242011-04-02 17:58:04 +0200100 #gtt_match{dpc = Dpc, ssn = Ssn} = Match,
101 Gt = SccpAddr#sccp_addr.global_title,
102 % First match the GT part
103 case single_gt_match(Match, Gt) of
104 false ->
105 false;
106 true ->
107 % build a list of the individual criteria that all have to match
Harald Welte2da7a852011-04-06 17:18:13 +0200108 SubMatchList = [{dpc, Dpc, SccpAddr#sccp_addr.point_code},
109 {ssn, Ssn, SccpAddr#sccp_addr.ssn}],
Harald Welte24a49242011-04-02 17:58:04 +0200110 gt_sub_match_list(SubMatchList)
111 end.
Harald Welte1f47f672011-04-02 14:33:31 +0200112
113% iterate over the list of individual match criteria and call the match function
114gt_sub_match_list([]) ->
115 true;
116gt_sub_match_list([{What, MatchPart, GtPart}|SubMatchList]) ->
117 case gt_sub_match(What, MatchPart, GtPart) of
118 false ->
119 false;
120 true ->
121 gt_sub_match_list(SubMatchList)
122 end.
123
124% matching of the actual phone number digits
125gt_sub_match(digits, {DigitsFrom, DigitsTo}, GtPart) ->
126 PhoneNumInt = osmo_util:digit_list2int(GtPart),
127 if
128 PhoneNumInt >= DigitsFrom, PhoneNumInt =< DigitsTo -> true;
129 true -> false
130 end;
131% any match that is not qualified will always match
132gt_sub_match(_What, undefined, _GtPart) ->
133 true;
134% remaining default match for all other fields
135gt_sub_match(_What, MatchPart, GtPart) ->
136 if
137 MatchPart == GtPart -> true;
138 true -> false
139 end.
140
141
142% Execute a single action: Replac some digits in the GT
Harald Welte6e508b62011-04-16 14:11:05 +0200143gtt_action(Gt, Action) when is_record(Gt, global_title),
144 is_record(Action, gtt_act_repl_digits) ->
Harald Welte1f47f672011-04-02 14:33:31 +0200145 #gtt_act_repl_digits{replace_digit_start = ReplDigStart,
146 replace_digit_end = ReplDigEnd,
147 new_digits = NewDigits} = Action,
148 GtDigitList = Gt#global_title.phone_number,
149 Header = lists:sublist(GtDigitList, 1, ReplDigStart-1),
150 Trailer = lists:sublist(GtDigitList, ReplDigEnd+1, length(GtDigitList)),
151 Gt#global_title{phone_number = Header ++ NewDigits ++ Trailer};
152
153% Execute a single action: Replac the numbering plan in the GT
Harald Welte6e508b62011-04-16 14:11:05 +0200154gtt_action(Gt, #gtt_act_repl_num_plan{numbering_plan = NewNumPlan})
155 when is_record(Gt, global_title) ->
Harald Welte7a321db2011-04-02 18:15:04 +0200156 Gt#global_title{numbering_plan = NewNumPlan};
157
158% Execute a single 'generic purpose' action that will call apply/2
Harald Welte6e508b62011-04-16 14:11:05 +0200159gtt_action(Gt, #gtt_act_apply{funct = Funct, args = Args}) when
160 is_record(Gt, global_title) ->
Harald Welte7a321db2011-04-02 18:15:04 +0200161 apply(Funct, Args).
162
Harald Welte1f47f672011-04-02 14:33:31 +0200163
164% appliy a list of GTT actions to a Global Title
165apply_gtt_actions(Gt, []) when is_record(Gt, global_title) ->
166 Gt;
167apply_gtt_actions(Gt, [Head|List]) when is_record(Gt, global_title) ->
168 NewGt = gtt_action(Gt, Head),
169 apply_gtt_actions(NewGt, List);
170apply_gtt_actions(Gt, Action) when is_record(Gt, global_title) ->
171 gtt_action(Gt, Action).
172
173% Execute a complete GTT operation: matching + executing the action
Harald Welte6e508b62011-04-16 14:11:05 +0200174execute_gtt(Gt, RulesList) when is_record(Gt, global_title),
175 is_list(RulesList) ->
Harald Welte1f47f672011-04-02 14:33:31 +0200176 case global_title_match(RulesList, Gt) of
177 false ->
178 Gt;
179 Action ->
180 apply_gtt_actions(Gt, Action)
Harald Welte24a49242011-04-02 17:58:04 +0200181 end;
182% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +0200183execute_gtt(SccpAddr, RulesList) when is_record(SccpAddr, sccp_addr),
184 is_list(RulesList) ->
Harald Welte24a49242011-04-02 17:58:04 +0200185 Gt = SccpAddr#sccp_addr.global_title,
186 NewGt = execute_gtt(Gt, RulesList),
187 SccpAddr#sccp_addr{global_title = NewGt}.