Add a new GTT module for GT matching + GT translation (GTT)
diff --git a/include/gtt.hrl b/include/gtt.hrl
new file mode 100644
index 0000000..5edeba7
--- /dev/null
+++ b/include/gtt.hrl
@@ -0,0 +1,20 @@
+% Record describing a GTT match
+-record(gtt_match, {
+	 gt_range_from,		% integer(), GT range lower boundary, included
+	 gt_range_to,		% integer(), GT range upper boundary, included
+	 numbering_plan,	% integer()
+	 nature_of_addr_ind,	% integer()
+	 dpc,			% integer()
+	 ssn}).
+
+% GTT action for replacing some digits
+-record(gtt_act_repl_digits, {
+	 replace_digit_start,	% integer(), digit from which we should replace
+	 replace_digit_end,	% integer
+	 new_digits		% list of integers
+	}).
+
+% GTT action for replacing the numbering plan
+-record(gtt_act_repl_num_plan, {
+	 numbering_plan
+	}).
diff --git a/src/osmo_ss7_gtt.erl b/src/osmo_ss7_gtt.erl
new file mode 100644
index 0000000..f1d2725
--- /dev/null
+++ b/src/osmo_ss7_gtt.erl
@@ -0,0 +1,118 @@
+% Osmocom Global Title Translation
+
+% (C) 2011 by Harald Welte <laforge@gnumonks.org>
+%
+% All Rights Reserved
+%
+% This program is free software; you can redistribute it and/or modify
+% it under the terms of the GNU Affero General Public License as
+% published by the Free Software Foundation; either version 3 of the
+% License, or (at your option) any later version.
+%
+% This program is distributed in the hope that it will be useful,
+% but WITHOUT ANY WARRANTY; without even the implied warranty of
+% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+% GNU General Public License for more details.
+%
+% You should have received a copy of the GNU Affero General Public License
+% along with this program.  If not, see <http://www.gnu.org/licenses/>.
+
+-module(osmo_ss7_gtt).
+-author('Harald Welte <laforge@gnumonks.org>').
+
+-include("sccp.hrl").
+-include("gtt.hrl").
+
+-export([global_title_match/2, apply_gtt_actions/2, execute_gtt/2]).
+
+% Match a given GT against an ordered list of {match, action} tuples
+global_title_match([], Gt) when is_record(Gt, global_title) ->
+	false;
+global_title_match([{Match, Action}|Tail], Gt) when is_record(Gt, global_title) ->
+	PhoneNumInt = osmo_util:digit_list2int(Gt#global_title.phone_number),
+	if Match#gtt_match.gt_range_from >= PhoneNumInt ->
+		% in an ordered list, we can assume that no trailing rules will match
+		false;
+	   true ->
+		case single_gt_match(Match, Gt) of
+		    true ->
+			Action;
+		    _ ->
+			% iterate further over the list of GTT rules
+			global_title_match(Tail, Gt)
+		end
+	end.
+
+% perform matching of a given global title against a single match
+single_gt_match(Match, Gt) when is_record(Match, gtt_match), is_record(Gt, global_title) ->
+	#gtt_match{gt_range_from = RangeFrom, gt_range_to = RangeTo,
+		   numbering_plan = NumPlan, nature_of_addr_ind = NatureInd,
+		   dpc = Dpc, ssn = Ssn} = Match,
+	% build a list of the individual criteria that all have to match
+	SubMatchList = [{digits, {RangeFrom, RangeTo}, Gt#global_title.phone_number},
+			{numbering_plan, NumPlan, Gt#global_title.numbering_plan},
+			{nature_of_addr_ind, NatureInd, Gt#global_title.nature_of_addr_ind}],
+	gt_sub_match_list(SubMatchList).
+
+% iterate over the list of individual match criteria and call the match function
+gt_sub_match_list([]) ->
+	true;
+gt_sub_match_list([{What, MatchPart, GtPart}|SubMatchList]) ->
+	case gt_sub_match(What, MatchPart, GtPart) of
+		false ->
+			false;
+		true ->
+			gt_sub_match_list(SubMatchList)
+	end.
+
+% matching of the actual phone number digits
+gt_sub_match(digits, {DigitsFrom, DigitsTo}, GtPart) ->
+	PhoneNumInt = osmo_util:digit_list2int(GtPart),
+	if
+		PhoneNumInt >= DigitsFrom, PhoneNumInt =< DigitsTo -> true;
+		true -> false
+	end;
+% any match that is not qualified will always match
+gt_sub_match(_What, undefined, _GtPart) ->
+	true;
+% remaining default match for all other fields
+gt_sub_match(_What, MatchPart, GtPart) ->
+	if
+		MatchPart == GtPart -> true;
+		true -> false
+	end.
+
+
+% Execute a single action: Replac some digits in the GT
+gtt_action(Gt, Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_digits) ->
+	#gtt_act_repl_digits{replace_digit_start = ReplDigStart,
+			   replace_digit_end = ReplDigEnd,
+			   new_digits = NewDigits} = Action,
+	GtDigitList = Gt#global_title.phone_number,
+	Header = lists:sublist(GtDigitList, 1, ReplDigStart-1),
+	Trailer = lists:sublist(GtDigitList, ReplDigEnd+1, length(GtDigitList)),
+	Gt#global_title{phone_number = Header ++ NewDigits ++ Trailer};
+
+% Execute a single action: Replac the numbering plan in the GT
+gtt_action(Gt,Action) when is_record(Gt, global_title), is_record(Action, gtt_act_repl_num_plan) ->
+	NewNumPlan = Action#gtt_act_repl_num_plan.numbering_plan,
+	Gt#global_title{numbering_plan = NewNumPlan}.
+
+% appliy a list of GTT actions to a Global Title
+apply_gtt_actions(Gt, []) when is_record(Gt, global_title) ->
+	Gt;
+apply_gtt_actions(Gt, [Head|List]) when is_record(Gt, global_title) ->
+	NewGt = gtt_action(Gt, Head),
+	apply_gtt_actions(NewGt, List);
+apply_gtt_actions(Gt, Action) when is_record(Gt, global_title) ->
+	gtt_action(Gt, Action).
+
+% Execute a complete GTT operation: matching + executing the action
+execute_gtt(Gt, RulesList) when is_record(Gt, global_title), is_list(RulesList) ->
+	case global_title_match(RulesList, Gt) of
+	    false ->
+		Gt;
+	    Action ->
+		apply_gtt_actions(Gt, Action)
+	end.
+