blob: 6c14dbdb403c2729bfdc675a2cd14c0798633347 [file] [log] [blame]
Harald Welte99f21c62011-02-03 19:05:33 +01001% ITU-T Q.71x SCCP UDT stateful masquerading
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(sccp_masq).
21-author('Harald Welte <laforge@gnumonks.org>').
22-include("sccp.hrl").
23
24-export([sccp_masq_msg/3, init/0]).
25
26-compile([export_all]).
27
28-record(sccp_masq_rec, {
29 digits_in, % list of GT digits
30 digits_out, % list of GT digits
31 last_access % timestamp of last usage
32 }).
33
34% Convert a list of digits to an integer value
35digit_list2int(Int, []) ->
36 Int;
37digit_list2int(Int, [Digit|Tail]) ->
38 digit_list2int(Int*10 + Digit, Tail).
39digit_list2int(Digits) when is_list(Digits) ->
40 digit_list2int(0, Digits).
41
42% Convert an integer value into a list of decimal digits
43int2digit_list(0, Digits) when is_list(Digits) ->
44 Digits;
45int2digit_list(Int, Digits) when is_integer(Int), is_list(Digits) ->
46 Digit = Int rem 10,
47 int2digit_list(Int div 10, [Digit|Digits]).
48int2digit_list(Int) when is_integer(Int) ->
49 int2digit_list(Int, []).
50
51-define(MASQ_GT_BASE, 12340000).
52-define(MASQ_GT_MAX, 9999).
53
54% alloc + insert a new masquerade state record in our tables
55masq_alloc(DigitsOrig) ->
56 masq_try_alloc(DigitsOrig, 0).
57masq_try_alloc(_DigitsOrig, Offset) when Offset > ?MASQ_GT_MAX ->
58 undef;
59masq_try_alloc(DigitsOrig, Offset) ->
60 Try = ?MASQ_GT_BASE + Offset,
61 TryDigits = int2digit_list(Try),
62 EtsRet = ets:insert_new(get(sccp_masq_orig),
63 #sccp_masq_rec{digits_in = DigitsOrig,
64 digits_out = TryDigits}),
65 case EtsRet of
66 false ->
67 masq_try_alloc(DigitsOrig, Offset+1);
68 _ ->
69 ets:insert(get(sccp_masq_rev),
70 #sccp_masq_rec{digits_in = TryDigits,
71 digits_out = DigitsOrig}),
72 TryDigits
73 end.
74
75% lookup a masqerade state record
76lookup_masq_addr(orig, GtDigits) ->
77 case ets:lookup(get(sccp_masq_orig), GtDigits) of
78 [#sccp_masq_rec{digits_out = DigitsOut}] ->
79 DigitsOut;
80 _ ->
81 % allocate a new masq GT
82 masq_alloc(GtDigits)
83 end;
84lookup_masq_addr(rev, GtDigits) ->
85 case ets:lookup(get(sccp_masq_rev), GtDigits) of
86 [#sccp_masq_rec{digits_out = DigitsOut}] ->
87 DigitsOut;
88 _ ->
89 % we do not allocate entries in the reverse direction
90 undef
91 end.
92
93
94% Masquerade the CALLING address in first STP(G-MSC) -> HLR/VLR/MSC dir
95mangle_rx_calling(from_stp, Addr = #sccp_addr{global_title = GT}) ->
96 GtOrig = GT#global_title.phone_number,
97 GtReplace = lookup_masq_addr(orig, GtOrig),
98 case GtReplace of
99 undef ->
100 io:format("SCCP MASQ: Unable to rewrite in original direction (out of GT addrs?)~n"),
101 Addr;
102 _ ->
103 io:format("SCCP MASQ (STP->MSC) rewrite ~p~n", [GtReplace]),
104 GTout = GT#global_title{phone_number = GtReplace},
105 Addr#sccp_addr{global_title = GTout}
106 end;
107mangle_rx_calling(_From, Addr) ->
108 Addr.
109
110mangle_rx_called(from_msc, Addr = #sccp_addr{global_title = GT}) ->
111 GtOrig = GT#global_title.phone_number,
112 GtReplace = lookup_masq_addr(rev, GtOrig),
113 case GtReplace of
114 undef ->
115 io:format("SCCP MASQ: Unable to rewrite in original direction (unknown GT ~p)~n", [GT]),
116 Addr;
117 _ ->
118 io:format("SCCP MASQ (MSC->STP) rewrite ~p~n", [GtReplace]),
119 GTout = GT#global_title{phone_number = GtReplace},
120 Addr#sccp_addr{global_title = GTout}
121 end;
122mangle_rx_called(_From, Addr) ->
123 Addr.
124
125
126sccp_masq_msg(From, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
127 CalledParty = proplists:get_value(called_party_addr, Opts),
128 CalledPartyNew = mangle_rx_called(From, CalledParty),
129 CallingParty = proplists:get_value(calling_party_addr, Opts),
130 CallingPartyNew = mangle_rx_calling(From, CallingParty),
131 Opts1 = lists:keyreplace(called_party_addr, 1, Opts,
132 {called_party_addr, CalledPartyNew}),
133 Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
134 {calling_party_addr, CallingPartyNew}),
135 Msg#sccp_msg{parameters = Opts2};
136sccp_masq_msg(_From, _MsgType, Msg) ->
137 Msg.
138
139init() ->
140 Orig = ets:new(sccp_masq_orig, [ordered_set,
141 {keypos, #sccp_masq_rec.digits_in}]),
142 Rev = ets:new(sccp_masq_rev, [ordered_set,
143 {keypos, #sccp_masq_rec.digits_in}]),
144 put(sccp_masq_orig, Orig),
145 put(sccp_masq_rev, Rev),
146 ok.