blob: 8cac7b178a852d30b0cbc10f274caeab48b8279f [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
Harald Weltea6b0da72011-02-04 18:08:52 +010024-export([sccp_masq_msg/3, init/0, reset/0]).
Harald Welte99f21c62011-02-03 19:05:33 +010025
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
Harald Welte99f21c62011-02-03 19:05:33 +010034-define(MASQ_GT_BASE, 12340000).
35-define(MASQ_GT_MAX, 9999).
36
37% alloc + insert a new masquerade state record in our tables
38masq_alloc(DigitsOrig) ->
39 masq_try_alloc(DigitsOrig, 0).
40masq_try_alloc(_DigitsOrig, Offset) when Offset > ?MASQ_GT_MAX ->
41 undef;
42masq_try_alloc(DigitsOrig, Offset) ->
43 Try = ?MASQ_GT_BASE + Offset,
Harald Welte99f21c62011-02-03 19:05:33 +010044 EtsRet = ets:insert_new(get(sccp_masq_orig),
45 #sccp_masq_rec{digits_in = DigitsOrig,
Harald Weltee60be422011-02-06 22:02:35 +010046 digits_out = Try}),
Harald Welte99f21c62011-02-03 19:05:33 +010047 case EtsRet of
48 false ->
49 masq_try_alloc(DigitsOrig, Offset+1);
50 _ ->
51 ets:insert(get(sccp_masq_rev),
Harald Weltee60be422011-02-06 22:02:35 +010052 #sccp_masq_rec{digits_in = Try,
Harald Welte99f21c62011-02-03 19:05:33 +010053 digits_out = DigitsOrig}),
Harald Weltee60be422011-02-06 22:02:35 +010054 Try
Harald Welte99f21c62011-02-03 19:05:33 +010055 end.
56
57% lookup a masqerade state record
58lookup_masq_addr(orig, GtDigits) ->
59 case ets:lookup(get(sccp_masq_orig), GtDigits) of
60 [#sccp_masq_rec{digits_out = DigitsOut}] ->
61 DigitsOut;
62 _ ->
63 % allocate a new masq GT
64 masq_alloc(GtDigits)
65 end;
66lookup_masq_addr(rev, GtDigits) ->
67 case ets:lookup(get(sccp_masq_rev), GtDigits) of
68 [#sccp_masq_rec{digits_out = DigitsOut}] ->
69 DigitsOut;
70 _ ->
71 % we do not allocate entries in the reverse direction
72 undef
73 end.
74
75
76% Masquerade the CALLING address in first STP(G-MSC) -> HLR/VLR/MSC dir
77mangle_rx_calling(from_stp, Addr = #sccp_addr{global_title = GT}) ->
78 GtOrig = GT#global_title.phone_number,
79 GtReplace = lookup_masq_addr(orig, GtOrig),
80 case GtReplace of
81 undef ->
82 io:format("SCCP MASQ: Unable to rewrite in original direction (out of GT addrs?)~n"),
83 Addr;
84 _ ->
85 io:format("SCCP MASQ (STP->MSC) rewrite ~p~n", [GtReplace]),
86 GTout = GT#global_title{phone_number = GtReplace},
87 Addr#sccp_addr{global_title = GTout}
88 end;
89mangle_rx_calling(_From, Addr) ->
90 Addr.
91
92mangle_rx_called(from_msc, Addr = #sccp_addr{global_title = GT}) ->
93 GtOrig = GT#global_title.phone_number,
94 GtReplace = lookup_masq_addr(rev, GtOrig),
95 case GtReplace of
96 undef ->
97 io:format("SCCP MASQ: Unable to rewrite in original direction (unknown GT ~p)~n", [GT]),
98 Addr;
99 _ ->
100 io:format("SCCP MASQ (MSC->STP) rewrite ~p~n", [GtReplace]),
101 GTout = GT#global_title{phone_number = GtReplace},
102 Addr#sccp_addr{global_title = GTout}
103 end;
104mangle_rx_called(_From, Addr) ->
105 Addr.
106
107
108sccp_masq_msg(From, ?SCCP_MSGT_UDT, Msg = #sccp_msg{parameters = Opts}) ->
109 CalledParty = proplists:get_value(called_party_addr, Opts),
110 CalledPartyNew = mangle_rx_called(From, CalledParty),
111 CallingParty = proplists:get_value(calling_party_addr, Opts),
112 CallingPartyNew = mangle_rx_calling(From, CallingParty),
113 Opts1 = lists:keyreplace(called_party_addr, 1, Opts,
114 {called_party_addr, CalledPartyNew}),
115 Opts2 = lists:keyreplace(calling_party_addr, 1, Opts1,
116 {calling_party_addr, CallingPartyNew}),
117 Msg#sccp_msg{parameters = Opts2};
118sccp_masq_msg(_From, _MsgType, Msg) ->
119 Msg.
120
121init() ->
122 Orig = ets:new(sccp_masq_orig, [ordered_set,
123 {keypos, #sccp_masq_rec.digits_in}]),
124 Rev = ets:new(sccp_masq_rev, [ordered_set,
125 {keypos, #sccp_masq_rec.digits_in}]),
126 put(sccp_masq_orig, Orig),
127 put(sccp_masq_rev, Rev),
128 ok.
Harald Weltea6b0da72011-02-04 18:08:52 +0100129
130reset() ->
131 io:format("SCCP MASQ: Deleting all MASQ state records~n"),
132 ets:delete_all_objects(get(sccp_masq_orig)),
133 ets:delete_all_objects(get(sccp_masq_rev)).