blob: f1d2725a0cc9225ec41904caf43708a281fc8bff [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/>.
19
20-module(osmo_ss7_gtt).
21-author('Harald Welte <laforge@gnumonks.org>').
22
23-include("sccp.hrl").
24-include("gtt.hrl").
25
26-export([global_title_match/2, apply_gtt_actions/2, execute_gtt/2]).
27
28% Match a given GT against an ordered list of {match, action} tuples
29global_title_match([], Gt) when is_record(Gt, global_title) ->
30 false;
31global_title_match([{Match, Action}|Tail], Gt) when is_record(Gt, global_title) ->
32 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
33 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
34 % in an ordered list, we can assume that no trailing rules will match
35 false;
36 true ->
37 case single_gt_match(Match, Gt) of
38 true ->
39 Action;
40 _ ->
41 % iterate further over the list of GTT rules
42 global_title_match(Tail, Gt)
43 end
44 end.
45
46% perform matching of a given global title against a single match
47single_gt_match(Match, Gt) when is_record(Match, gtt_match), is_record(Gt, global_title) ->
48 #gtt_match{gt_range_from = RangeFrom, gt_range_to = RangeTo,
49 numbering_plan = NumPlan, nature_of_addr_ind = NatureInd,
50 dpc = Dpc, ssn = Ssn} = Match,
51 % build a list of the individual criteria that all have to match
52 SubMatchList = [{digits, {RangeFrom, RangeTo}, Gt#global_title.phone_number},
53 {numbering_plan, NumPlan, Gt#global_title.numbering_plan},
54 {nature_of_addr_ind, NatureInd, Gt#global_title.nature_of_addr_ind}],
55 gt_sub_match_list(SubMatchList).
56
57% iterate over the list of individual match criteria and call the match function
58gt_sub_match_list([]) ->
59 true;
60gt_sub_match_list([{What, MatchPart, GtPart}|SubMatchList]) ->
61 case gt_sub_match(What, MatchPart, GtPart) of
62 false ->
63 false;
64 true ->
65 gt_sub_match_list(SubMatchList)
66 end.
67
68% matching of the actual phone number digits
69gt_sub_match(digits, {DigitsFrom, DigitsTo}, GtPart) ->
70 PhoneNumInt = osmo_util:digit_list2int(GtPart),
71 if
72 PhoneNumInt >= DigitsFrom, PhoneNumInt =< DigitsTo -> true;
73 true -> false
74 end;
75% any match that is not qualified will always match
76gt_sub_match(_What, undefined, _GtPart) ->
77 true;
78% remaining default match for all other fields
79gt_sub_match(_What, MatchPart, GtPart) ->
80 if
81 MatchPart == GtPart -> true;
82 true -> false
83 end.
84
85
86% Execute a single action: Replac some digits in the GT
87gtt_action(Gt, Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_digits) ->
88 #gtt_act_repl_digits{replace_digit_start = ReplDigStart,
89 replace_digit_end = ReplDigEnd,
90 new_digits = NewDigits} = Action,
91 GtDigitList = Gt#global_title.phone_number,
92 Header = lists:sublist(GtDigitList, 1, ReplDigStart-1),
93 Trailer = lists:sublist(GtDigitList, ReplDigEnd+1, length(GtDigitList)),
94 Gt#global_title{phone_number = Header ++ NewDigits ++ Trailer};
95
96% Execute a single action: Replac the numbering plan in the GT
97gtt_action(Gt,Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_num_plan) ->
98 NewNumPlan = Action#gtt_act_repl_num_plan.numbering_plan,
99 Gt#global_title{numbering_plan = NewNumPlan}.
100
101% appliy a list of GTT actions to a Global Title
102apply_gtt_actions(Gt, []) when is_record(Gt, global_title) ->
103 Gt;
104apply_gtt_actions(Gt, [Head|List]) when is_record(Gt, global_title) ->
105 NewGt = gtt_action(Gt, Head),
106 apply_gtt_actions(NewGt, List);
107apply_gtt_actions(Gt, Action) when is_record(Gt, global_title) ->
108 gtt_action(Gt, Action).
109
110% Execute a complete GTT operation: matching + executing the action
111execute_gtt(Gt, RulesList) when is_record(Gt, global_title), is_list(RulesList) ->
112 case global_title_match(RulesList, Gt) of
113 false ->
114 Gt;
115 Action ->
116 apply_gtt_actions(Gt, Action)
117 end.
118