blob: a3e97854effe8aa866f319f94709fc1c4561f1cf [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 ->
Harald Welte6e508b62011-04-16 14:11:05 +020037 % in an ordered list, we can assume that no trailing rules will
38 % match
Harald Welte1f47f672011-04-02 14:33:31 +020039 false;
40 true ->
41 case single_gt_match(Match, Gt) of
42 true ->
43 Action;
44 _ ->
45 % iterate further over the list of GTT rules
46 global_title_match(Tail, Gt)
47 end
Harald Welte24a49242011-04-02 17:58:04 +020048 end;
49% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +020050global_title_match([{Match, Action}|Tail], SccpAddr) when
51 is_record(SccpAddr, sccp_addr) ->
Harald Welte24a49242011-04-02 17:58:04 +020052 Gt = SccpAddr#sccp_addr.global_title,
53 PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
54 if Match#gtt_match.gt_range_from >= PhoneNumInt ->
Harald Welte6e508b62011-04-16 14:11:05 +020055 % in an ordered list, we can assume that no trailing rules will
56 % match
Harald Welte24a49242011-04-02 17:58:04 +020057 false;
58 true ->
59 case single_gt_match(Match, SccpAddr) of
60 true ->
61 Action;
62 _ ->
63 % iterate further over the list of GTT rules
64 global_title_match(Tail, SccpAddr)
65 end
Harald Welte1f47f672011-04-02 14:33:31 +020066 end.
67
Harald Welte24a49242011-04-02 17:58:04 +020068
Harald Welte1f47f672011-04-02 14:33:31 +020069% perform matching of a given global title against a single match
Harald Welte6e508b62011-04-16 14:11:05 +020070single_gt_match(Match, Gt) when is_record(Match, gtt_match),
71 is_record(Gt, global_title) ->
Harald Welte1f47f672011-04-02 14:33:31 +020072 #gtt_match{gt_range_from = RangeFrom, gt_range_to = RangeTo,
Harald Welte6e508b62011-04-16 14:11:05 +020073 numbering_plan = NumPlan,
74 nature_of_addr_ind = NatureInd} = Match,
75 #global_title{phone_number = GtPhoneNum,
76 numbering_plan = GtNumPlan,
77 nature_of_addr_ind = GtNature} = Gt,
Harald Welte1f47f672011-04-02 14:33:31 +020078 % build a list of the individual criteria that all have to match
Harald Welte6e508b62011-04-16 14:11:05 +020079 SubMatchList = [{digits, {RangeFrom, RangeTo}, GtPhoneNum},
80 {numbering_plan, NumPlan, GtNumPlan},
81 {nature_of_addr_ind, NatureInd, GtNature}],
Harald Welte24a49242011-04-02 17:58:04 +020082 gt_sub_match_list(SubMatchList);
83% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +020084single_gt_match(Match, SccpAddr) when is_record(Match, gtt_match),
85 is_record(SccpAddr, sccp_addr) ->
Harald Welte24a49242011-04-02 17:58:04 +020086 #gtt_match{dpc = Dpc, ssn = Ssn} = Match,
87 Gt = SccpAddr#sccp_addr.global_title,
88 % First match the GT part
89 case single_gt_match(Match, Gt) of
90 false ->
91 false;
92 true ->
93 % build a list of the individual criteria that all have to match
Harald Welte2da7a852011-04-06 17:18:13 +020094 SubMatchList = [{dpc, Dpc, SccpAddr#sccp_addr.point_code},
95 {ssn, Ssn, SccpAddr#sccp_addr.ssn}],
Harald Welte24a49242011-04-02 17:58:04 +020096 gt_sub_match_list(SubMatchList)
97 end.
Harald Welte1f47f672011-04-02 14:33:31 +020098
99% iterate over the list of individual match criteria and call the match function
100gt_sub_match_list([]) ->
101 true;
102gt_sub_match_list([{What, MatchPart, GtPart}|SubMatchList]) ->
103 case gt_sub_match(What, MatchPart, GtPart) of
104 false ->
105 false;
106 true ->
107 gt_sub_match_list(SubMatchList)
108 end.
109
110% matching of the actual phone number digits
111gt_sub_match(digits, {DigitsFrom, DigitsTo}, GtPart) ->
112 PhoneNumInt = osmo_util:digit_list2int(GtPart),
113 if
114 PhoneNumInt >= DigitsFrom, PhoneNumInt =< DigitsTo -> true;
115 true -> false
116 end;
117% any match that is not qualified will always match
118gt_sub_match(_What, undefined, _GtPart) ->
119 true;
120% remaining default match for all other fields
121gt_sub_match(_What, MatchPart, GtPart) ->
122 if
123 MatchPart == GtPart -> true;
124 true -> false
125 end.
126
127
128% Execute a single action: Replac some digits in the GT
Harald Welte6e508b62011-04-16 14:11:05 +0200129gtt_action(Gt, Action) when is_record(Gt, global_title),
130 is_record(Action, gtt_act_repl_digits) ->
Harald Welte1f47f672011-04-02 14:33:31 +0200131 #gtt_act_repl_digits{replace_digit_start = ReplDigStart,
132 replace_digit_end = ReplDigEnd,
133 new_digits = NewDigits} = Action,
134 GtDigitList = Gt#global_title.phone_number,
135 Header = lists:sublist(GtDigitList, 1, ReplDigStart-1),
136 Trailer = lists:sublist(GtDigitList, ReplDigEnd+1, length(GtDigitList)),
137 Gt#global_title{phone_number = Header ++ NewDigits ++ Trailer};
138
139% Execute a single action: Replac the numbering plan in the GT
Harald Welte6e508b62011-04-16 14:11:05 +0200140gtt_action(Gt, #gtt_act_repl_num_plan{numbering_plan = NewNumPlan})
141 when is_record(Gt, global_title) ->
Harald Welte7a321db2011-04-02 18:15:04 +0200142 Gt#global_title{numbering_plan = NewNumPlan};
143
144% Execute a single 'generic purpose' action that will call apply/2
Harald Welte6e508b62011-04-16 14:11:05 +0200145gtt_action(Gt, #gtt_act_apply{funct = Funct, args = Args}) when
146 is_record(Gt, global_title) ->
Harald Welte7a321db2011-04-02 18:15:04 +0200147 apply(Funct, Args).
148
Harald Welte1f47f672011-04-02 14:33:31 +0200149
150% appliy a list of GTT actions to a Global Title
151apply_gtt_actions(Gt, []) when is_record(Gt, global_title) ->
152 Gt;
153apply_gtt_actions(Gt, [Head|List]) when is_record(Gt, global_title) ->
154 NewGt = gtt_action(Gt, Head),
155 apply_gtt_actions(NewGt, List);
156apply_gtt_actions(Gt, Action) when is_record(Gt, global_title) ->
157 gtt_action(Gt, Action).
158
159% Execute a complete GTT operation: matching + executing the action
Harald Welte6e508b62011-04-16 14:11:05 +0200160execute_gtt(Gt, RulesList) when is_record(Gt, global_title),
161 is_list(RulesList) ->
Harald Welte1f47f672011-04-02 14:33:31 +0200162 case global_title_match(RulesList, Gt) of
163 false ->
164 Gt;
165 Action ->
166 apply_gtt_actions(Gt, Action)
Harald Welte24a49242011-04-02 17:58:04 +0200167 end;
168% Same as above, but for SCCP Address (i.e. GT + point code and SSN)
Harald Welte6e508b62011-04-16 14:11:05 +0200169execute_gtt(SccpAddr, RulesList) when is_record(SccpAddr, sccp_addr),
170 is_list(RulesList) ->
Harald Welte24a49242011-04-02 17:58:04 +0200171 Gt = SccpAddr#sccp_addr.global_title,
172 NewGt = execute_gtt(Gt, RulesList),
173 SccpAddr#sccp_addr{global_title = NewGt}.