blob: 00d2c2dc1244a24191d08f990ea407432d8e5d37 [file] [log] [blame]
Harald Welte5df83382011-03-08 15:17:32 +01001% VFUK-ONW specific mgw_nat actor callback functions
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4% (C) 2011 OnWaves
5%
6% All Rights Reserved
7%
8% This program is free software; you can redistribute it and/or modify
9% it under the terms of the GNU Affero General Public License as
10% published by the Free Software Foundation; either version 3 of the
11% License, or (at your option) any later version.
12%
13% This program is distributed in the hope that it will be useful,
14% but WITHOUT ANY WARRANTY; without even the implied warranty of
15% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16% GNU General Public License for more details.
17%
18% You should have received a copy of the GNU Affero General Public License
19% along with this program. If not, see <http://www.gnu.org/licenses/>.
Harald Welte0b452a82012-04-16 13:17:31 +020020%
21% Additional Permission under GNU AGPL version 3 section 7:
22%
23% If you modify this Program, or any covered work, by linking or
24% combining it with runtime libraries of Erlang/OTP as released by
25% Ericsson on http://www.erlang.org (or a modified version of these
26% libraries), containing parts covered by the terms of the Erlang Public
27% License (http://www.erlang.org/EPLICENSE), the licensors of this
28% Program grant you additional permission to convey the resulting work
29% without the need to license the runtime libraries of Erlang/OTP under
30% the GNU Affero General Public License. Corresponding Source for a
31% non-source form of such a combination shall include the source code
32% for the parts of the runtime libraries of Erlang/OTP used as well as
33% that of the covered work.
Harald Welte5df83382011-03-08 15:17:32 +010034
35-module(mgw_nat_act_vfuk_onw).
36-author("Harald Welte <laforge@gnumonks.org>").
37
Harald Welte99e92c22011-04-06 17:22:30 +020038-export([rewrite_actor/5, reload_config/0]).
Harald Welte93db48d2011-03-10 00:47:36 +010039-export([camelph_twalk_cb/3]).
40
41-include_lib("osmo_map/include/map.hrl").
42-include_lib("osmo_ss7/include/sccp.hrl").
Harald Welte5df83382011-03-08 15:17:32 +010043
44% Rewrite at SCTP (root) level:
45rewrite_actor(sctp, From, Path, 2, DataBin) ->
46 try mgw_nat:mangle_rx_data(From, Path, DataBin, fun rewrite_actor/5) of
47 Val ->
48 Val
49 catch error:Error ->
50 % some parser error, simply forward msg unmodified
Harald Welteeee3eac2011-03-12 10:34:33 +010051 error_logger:error_report([{error, Error},
Harald Welte92acea92011-04-14 17:50:09 +020052 {stacktrace, erlang:get_stacktrace()},
53 {from, From}, {path, Path},
54 {data_bin, DataBin}]),
Harald Welte5df83382011-03-08 15:17:32 +010055 DataBin
56 end;
57
Harald Welte6c202b22012-05-30 13:10:46 +020058% Rewrite at SCCP level: call into mangle_tt_sri_sm
59rewrite_actor(sccp, from_msc, Path, SccpType, SccpDec) ->
60 mangle_tt_sri_sm:mangle_tt_sri_sm(from_msc, Path, SccpType, SccpDec);
61
Harald Welte5df83382011-03-08 15:17:32 +010062% Rewrite at MAP level: call into map_masq module
63rewrite_actor(map, From, Path, 0, MapDec) ->
64 mangle_map_camel_phase(From, Path, MapDec);
65
66% Default action: no rewrite
67rewrite_actor(_Level, _From, _Path, _MsgType, Msg) ->
68 Msg.
69
70
Harald Welteeee3eac2011-03-12 10:34:33 +010071mangle_map_camel_phase(from_stp, _Path, MapDec) ->
Harald Welte93db48d2011-03-10 00:47:36 +010072 MapDec;
73mangle_map_camel_phase(from_msc, Path, MapDec) ->
74 % Resolve the Global Title of the SCCP Called Addr
Harald Welteeea20e12011-03-31 09:40:44 +020075 {value, #sccp_msg{parameters = SccpPars}} = lists:keysearch(sccp_msg, 1, Path),
Harald Welte93db48d2011-03-10 00:47:36 +010076 CalledAddr = proplists:get_value(called_party_addr, SccpPars),
Harald Welte99e92c22011-04-06 17:22:30 +020077 {ok, IntTbl} = application:get_env(mgw_nat, int_camel_ph_tbl),
78 case osmo_ss7_gtt:global_title_match(IntTbl, CalledAddr) of
Harald Welte93db48d2011-03-10 00:47:36 +010079 false ->
80 MapDec;
Harald Welte99e92c22011-04-06 17:22:30 +020081 PhaseL ->
82 #global_title{phone_number = PhoneNum} = CalledAddr#sccp_addr.global_title,
83 PhoneNumInt = osmo_util:digit_list2int(PhoneNum),
Harald Welteeea20e12011-03-31 09:40:44 +020084 io:format("Rewriting Camel Phase List to ~p, GT ~p~n", [PhaseL, PhoneNumInt]),
Harald Welte93db48d2011-03-10 00:47:36 +010085 osmo_util:tuple_walk(MapDec, fun camelph_twalk_cb/3, [PhaseL])
86 end.
87
Harald Welte99e92c22011-04-06 17:22:30 +020088
Harald Welte93db48d2011-03-10 00:47:36 +010089% tuple tree walker callback function
90camelph_twalk_cb(['begin','MapSpecificPDUs_begin',basicROS,invoke,
91 'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke',
92 'UpdateLocationArg'], VC = #'VLR-Capability'{}, [PhaseL|_Args]) ->
93 % Manipulate the VLR capabilities in UpdateLocationArg
94 VC#'VLR-Capability'{supportedCamelPhases = PhaseL};
95camelph_twalk_cb(_Path, Msg, _Args) ->
96 % Default case: simply return the unmodified tuple
97 Msg.
Harald Welte99e92c22011-04-06 17:22:30 +020098
99
100gen_int_camelph_tbl(L) ->
101 gen_int_camelph_tbl(L, []).
102gen_int_camelph_tbl([], Out) ->
103 Out;
104gen_int_camelph_tbl([{GttPart, PhasePart}|Tail], Out) ->
105 GttMatch = osmo_ss7_gtt:'#new-gtt_match'(GttPart),
106 % Fixme: use ordered insert!
107 gen_int_camelph_tbl(Tail, Out ++ [{GttMatch, PhasePart}]).
108
109reload_config() ->
110 {ok, CamelPatchTblIn} = application:get_env(mgw_nat, camel_phase_patch_table),
111 io:format("VFUK-ONW actor: reloading config ~p~n", [CamelPatchTblIn]),
112 try gen_int_camelph_tbl(CamelPatchTblIn) of
113 TblOut ->
114 application:set_env(mgw_nat, int_camel_ph_tbl, TblOut)
115 catch error:Error ->
116 error_logger:error_report([{error, Error},
117 {stacktrace, erlang:get_stacktrace()}])
118 end.