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