blob: fb117d4f678c4a07d51f34c08127bec55dcdbb90 [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
Harald Welte8e7cdaf2011-04-02 17:24:47 +020028-compile({parse_transform, exprecs}).
29-export_records([gtt_match, gtt_act_repl_digits, gtt_act_repl_num_plan]).
30
Harald Welte1f47f672011-04-02 14:33:31 +020031% Match a given GT against an ordered list of {match, action} tuples
Harald Welte24a49242011-04-02 17:58:04 +020032global_title_match([], _Gt) ->
Harald Welte1f47f672011-04-02 14:33:31 +020033 false;
34global_title_match([{Match, Action}|Tail], Gt) when is_record(Gt, global_title) ->
35 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
36 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
37 % in an ordered list, we can assume that no trailing rules will match
38 false;
39 true ->
40 case single_gt_match(Match, Gt) of
41 true ->
42 Action;
43 _ ->
44 % iterate further over the list of GTT rules
45 global_title_match(Tail, Gt)
46 end
Harald Welte24a49242011-04-02 17:58:04 +020047 end;
48% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
49global_title_match([{Match, Action}|Tail], SccpAddr) when is_record(SccpAddr, sccp_addr) ->
50 Gt = SccpAddr#sccp_addr.global_title,
51 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
52 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
53 % in an ordered list, we can assume that no trailing rules will match
54 false;
55 true ->
56 case single_gt_match(Match, SccpAddr) of
57 true ->
58 Action;
59 _ ->
60 % iterate further over the list of GTT rules
61 global_title_match(Tail, SccpAddr)
62 end
Harald Welte1f47f672011-04-02 14:33:31 +020063 end.
64
Harald Welte24a49242011-04-02 17:58:04 +020065
Harald Welte1f47f672011-04-02 14:33:31 +020066% perform matching of a given global title against a single match
67single_gt_match(Match, Gt) when is_record(Match, gtt_match), is_record(Gt, global_title) ->
68 #gtt_match{gt_range_from = RangeFrom, gt_range_to = RangeTo,
Harald Welte24a49242011-04-02 17:58:04 +020069 numbering_plan = NumPlan, nature_of_addr_ind = NatureInd} = Match,
Harald Welte1f47f672011-04-02 14:33:31 +020070 % build a list of the individual criteria that all have to match
71 SubMatchList = [{digits, {RangeFrom, RangeTo}, Gt#global_title.phone_number},
72 {numbering_plan, NumPlan, Gt#global_title.numbering_plan},
73 {nature_of_addr_ind, NatureInd, Gt#global_title.nature_of_addr_ind}],
Harald Welte24a49242011-04-02 17:58:04 +020074 gt_sub_match_list(SubMatchList);
75% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
76single_gt_match(Match, SccpAddr) when is_record(Match, gtt_match), is_record(SccpAddr, sccp_addr) ->
77 #gtt_match{dpc = Dpc, ssn = Ssn} = Match,
78 Gt = SccpAddr#sccp_addr.global_title,
79 % First match the GT part
80 case single_gt_match(Match, Gt) of
81 false ->
82 false;
83 true ->
84 % build a list of the individual criteria that all have to match
85 SubMatchList = [{dpc, Dpc}, {ssn, Ssn}],
86 gt_sub_match_list(SubMatchList)
87 end.
Harald Welte1f47f672011-04-02 14:33:31 +020088
89% iterate over the list of individual match criteria and call the match function
90gt_sub_match_list([]) ->
91 true;
92gt_sub_match_list([{What, MatchPart, GtPart}|SubMatchList]) ->
93 case gt_sub_match(What, MatchPart, GtPart) of
94 false ->
95 false;
96 true ->
97 gt_sub_match_list(SubMatchList)
98 end.
99
100% matching of the actual phone number digits
101gt_sub_match(digits, {DigitsFrom, DigitsTo}, GtPart) ->
102 PhoneNumInt = osmo_util:digit_list2int(GtPart),
103 if
104 PhoneNumInt >= DigitsFrom, PhoneNumInt =< DigitsTo -> true;
105 true -> false
106 end;
107% any match that is not qualified will always match
108gt_sub_match(_What, undefined, _GtPart) ->
109 true;
110% remaining default match for all other fields
111gt_sub_match(_What, MatchPart, GtPart) ->
112 if
113 MatchPart == GtPart -> true;
114 true -> false
115 end.
116
117
118% Execute a single action: Replac some digits in the GT
119gtt_action(Gt, Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_digits) ->
120 #gtt_act_repl_digits{replace_digit_start = ReplDigStart,
121 replace_digit_end = ReplDigEnd,
122 new_digits = NewDigits} = Action,
123 GtDigitList = Gt#global_title.phone_number,
124 Header = lists:sublist(GtDigitList, 1, ReplDigStart-1),
125 Trailer = lists:sublist(GtDigitList, ReplDigEnd+1, length(GtDigitList)),
126 Gt#global_title{phone_number = Header ++ NewDigits ++ Trailer};
127
128% Execute a single action: Replac the numbering plan in the GT
129gtt_action(Gt,Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_num_plan) ->
130 NewNumPlan = Action#gtt_act_repl_num_plan.numbering_plan,
131 Gt#global_title{numbering_plan = NewNumPlan}.
132
133% appliy a list of GTT actions to a Global Title
134apply_gtt_actions(Gt, []) when is_record(Gt, global_title) ->
135 Gt;
136apply_gtt_actions(Gt, [Head|List]) when is_record(Gt, global_title) ->
137 NewGt = gtt_action(Gt, Head),
138 apply_gtt_actions(NewGt, List);
139apply_gtt_actions(Gt, Action) when is_record(Gt, global_title) ->
140 gtt_action(Gt, Action).
141
142% Execute a complete GTT operation: matching + executing the action
143execute_gtt(Gt, RulesList) when is_record(Gt, global_title), is_list(RulesList) ->
144 case global_title_match(RulesList, Gt) of
145 false ->
146 Gt;
147 Action ->
148 apply_gtt_actions(Gt, Action)
Harald Welte24a49242011-04-02 17:58:04 +0200149 end;
150% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
151execute_gtt(SccpAddr, RulesList) when is_record(SccpAddr, sccp_addr), is_list(RulesList) ->
152 Gt = SccpAddr#sccp_addr.global_title,
153 NewGt = execute_gtt(Gt, RulesList),
154 SccpAddr#sccp_addr{global_title = NewGt}.