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