mgw_nat: Add ability to translate multiple signalling links

The mgw_nat_sup supervisor now starts one mgw_nat_usr process for each
MSC-STP link defined in the configuration file.  However, the actual
translation/mangling/masquerading configuration as well as runtime state
like allocated SCCP mappings is global/shared between all signalling
links.

Furthermore, a new mgw_nat_adm process is introduced to ensure config
file reloading (formerly handled by the single mgw_nat_usr) does not
have to run in the supervisor (and risk crashing it).
This commit is contained in:
Harald Welte 2011-09-15 00:15:29 +01:00
parent f83e20e307
commit ce995d3d30
5 changed files with 160 additions and 57 deletions

View File

@ -2,14 +2,12 @@
[{description, "Media Gateway NAT"},
{vsn, "1"},
{modules, [mgw_nat_app, mgw_nat_sup, mgw_nat_usr, mgw_nat,
sccp_masq, map_masq, sctp_handler,
mgw_nat_adm, sccp_masq, map_masq, sctp_handler,
mgw_nat_act_bow_onw, mgw_nat_act_vfuk_onw]},
{registered, [mgw_nat_app]},
{mod, {mgw_nat_app, []}},
{applications, []},
{env, [
% Specify the rewrite actor module
%{rewrite_act_mod, mgw_nat_act_bow_onw },
% SCCP static rewrite rules
{sccp_rewrite_tbl, [
@ -27,11 +25,26 @@
{intern_pfx, 63},
% Example SCTP / IP config
{msc_local_ip, any},
{msc_local_port, 2904},
{msc_remote_ip, {172,16,1,81}},
{stp_remote_ip, {172,16,249,20}},
{stp_remote_port, 2904},
{sign_links, [
{mgw_nat_msc1, [
{msc_local_ip, any},
{msc_local_port, 2904},
{msc_remote_ip, {172,16,1,81}},
{stp_remote_ip, {172,16,249,20}},
{stp_remote_port, 2904},
% Specify the rewrite actor module
{rewrite_act_mod, mgw_nat_act_bow_onw }
]},
{mgw_nat_msc2, [
{msc_local_ip, any},
{msc_local_port, 2905},
{msc_remote_ip, {172,16,1,81}},
%{stp_remote_ip, {172,16,249,20}},
{stp_remote_port, 2905},
% Specify the rewrite actor module
{rewrite_act_mod, mgw_nat_act_bow_onw }
]}
]},
% Example MAP rewrite table
{map_rewrite_table, [

82
src/mgw_nat_adm.erl Normal file
View File

@ -0,0 +1,82 @@
% Administrative process for MGW NAT
% The administrative process takes care of re-loading the configuration
% after it has been re-parsed. This includes delivering a reload_config
% signal to all child processes of the supervisor. We don't do this
% inside the supervisor itself, as there might be an exception.
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
% (C) 2011 OnWaves
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
-module(mgw_nat_adm).
-author("Harald Welte <laforge@gnumonks.org>").
-behaviour(gen_server).
-export([init/1, handle_cast/2, handle_info/2, terminate/2, start_link/1]).
-export([sccp_masq_reset/0, sccp_masq_dump/0, reload_config/0]).
sccp_masq_reset() ->
gen_server:cast(?MODULE, sccp_masq_reset).
sccp_masq_dump() ->
gen_server:cast(?MODULE, sccp_masq_dump).
reload_config() ->
gen_server:cast(?MODULE, reload_all_config).
start_link(Params) ->
gen_server:start_link({local, ?MODULE}, ?MODULE, Params, []).
init(_Params) ->
{ok, foo}.
handle_cast(sccp_masq_reset, LoopData) ->
sccp_masq:reset(),
{noreply, LoopData};
handle_cast(sccp_masq_dump, LoopData) ->
sccp_masq:dump(),
{noreply, LoopData};
handle_cast(reload_config, LoopData) ->
{noreply, LoopData};
handle_cast(reload_all_config, LoopData) ->
map_masq:config_update(),
% now we iterate over the children and deliver the signal
Children = supervisor:which_children(mgw_nat_sup),
cast_to_children(Children, reload_config),
% and finally return to the main loop
{noreply, LoopData}.
handle_info(Info, LoopData) ->
{noreply, LoopData}.
terminate(_Reason, _LoopData) ->
ok.
cast_to_children([], _Cast) ->
ok;
cast_to_children([Child|Tail], Cast) ->
{Name, Pid, _Type, _Modules} = Child,
io:format("Casting ~p to ~p(~p)~n", [Cast, Name, Pid]),
gen_server:cast(Pid, Cast),
cast_to_children(Tail, Cast).

View File

@ -14,5 +14,4 @@ stop(_State) ->
reload_config() ->
osmo_util:reload_config(),
mgw_nat_usr:reload_config(),
map_masq:config_update().
mgw_nat_adm:reload_config().

View File

@ -27,7 +27,33 @@
start_link() ->
supervisor:start_link({local, ?MODULE}, ?MODULE, []).
init(Args) ->
MgwChild = {mgw_nat_usr, {mgw_nat_usr, start_link, [Args]},
init(_Args) ->
sccp_masq:init(),
map_masq:config_update(),
SignLinkList = get_app_config(sign_links),
ChildList = gen_child_list(SignLinkList),
AdmChild = {mgw_nat_adm, {mgw_nat_adm, start_link, [foo]},
permanent, 2000, worker, [mgw_nat_usr, sctp_handler,
mgw_nat, mgw_nat_adm]},
{ok,{{one_for_one,60,600}, [AdmChild|ChildList]}}.
% generate a list of child specifications, one for each signalling link
gen_child_list(SignLinkList) ->
gen_child_list(SignLinkList, []).
gen_child_list([], ChildList) ->
ChildList;
gen_child_list([Link|Tail], ChildList) ->
{Name, ChildArgs} = Link,
NewChild = {Name, {mgw_nat_usr, start_link, [[{msc_name, Name}|ChildArgs]]},
permanent, 2000, worker, [mgw_nat_usr, sctp_handler, mgw_nat]},
{ok,{{one_for_all,60,600}, [MgwChild]}}.
gen_child_list(Tail, [NewChild|ChildList]).
get_app_config(Name) ->
case application:get_env(Name) of
undefined ->
error_logger:error_report([{error, app_cfg_missing},
{get_app_config, Name}]),
throw(app_cfg_missing);
{ok, Val} ->
Val
end.

View File

@ -23,74 +23,57 @@
-behavior(gen_server).
-export([start_link/1, stop/0, sccp_masq_reset/0, sccp_masq_dump/0,
reload_config/0]).
-export([start_link/1, stop/0]).
-export([init/1, handle_cast/2, handle_info/2, terminate/2]).
start_link(Params) ->
gen_server:start_link({local, ?MODULE}, ?MODULE, Params, []).
MscName = get_cfg_pl_val(msc_name, Params),
gen_server:start_link({local, MscName}, ?MODULE, Params, []).
stop() ->
gen_server:cast(?MODULE, stop).
sccp_masq_reset() ->
gen_server:cast(?MODULE, sccp_masq_reset).
sccp_masq_dump() ->
gen_server:cast(?MODULE, sccp_masq_dump).
reload_config() ->
gen_server:cast(?MODULE, reload_config).
%% Callback functions of the OTP behavior
init(_Params) ->
sccp_masq:init(),
map_masq:config_update(),
MscLocalIp = get_app_config(msc_local_ip),
MscLocalPort = get_app_config(msc_local_port),
MscRemoteIp = get_app_config(msc_remote_ip),
StpRemoteIp = get_app_config(stp_remote_ip),
StpRemotePort = get_app_config(stp_remote_port),
RewriteActMod = get_app_config(rewrite_act_mod),
init(Params) ->
io:format("Starting mgw_nat_usr with Args ~p~n", [Params]),
MscLocalIp = get_cfg_pl_val(msc_local_ip, Params),
MscLocalPort = get_cfg_pl_val(msc_local_port, Params),
MscRemoteIp = get_cfg_pl_val(msc_remote_ip, Params),
StpRemoteIp = get_cfg_pl_val(stp_remote_ip, Params),
StpRemotePort = get_cfg_pl_val(stp_remote_port, Params),
RewriteActMod = get_cfg_pl_val(rewrite_act_mod, Params),
RewriteActMod:reload_config(),
io:format("Starting mgw_nat_usr with rewrite actor module ~p~n", [RewriteActMod]),
SctpHdlrArgs = [MscLocalIp, MscLocalPort, MscRemoteIp,
StpRemoteIp, StpRemotePort, RewriteActMod],
apply(sctp_handler, init, SctpHdlrArgs).
LoopDat = apply(sctp_handler, init, SctpHdlrArgs),
{ok, {Params, LoopDat}}.
% this cast is produced by mgw_nat_sup child walker
handle_cast(reload_config, L = {Params, _LoopData}) ->
RewriteActMod = get_cfg_pl_val(rewrite_act_mod, Params),
RewriteActMod:reload_config(),
{noreply, L};
handle_cast(stop, LoopData) ->
{stop, normal, LoopData};
handle_cast(sccp_masq_reset, LoopData) ->
sccp_masq:reset(),
{noreply, LoopData};
handle_cast(sccp_masq_dump, LoopData) ->
sccp_masq:dump(),
{noreply, LoopData};
handle_cast(reload_config, LoopData) ->
RewriteActMod = get_app_config(rewrite_act_mod),
RewriteActMod:reload_config(),
{noreply, LoopData}.
{stop, normal, LoopData}.
terminate(_Reason, _LoopData) ->
ok.
% callback for other events like incoming SCTP message
handle_info({sctp, Sock, Ip, Port, Data}, LoopData) ->
handle_info({sctp, Sock, Ip, Port, Data}, {InitParams, LoopData}) ->
NewL = sctp_handler:handle_sctp(LoopData, {sctp, Sock, Ip, Port, Data}),
{noreply, NewL}.
{noreply, {InitParams, NewL}}.
get_app_config(Name) ->
case application:get_env(Name) of
% wrapper around proplists:get_value() to check for missing stuff
get_cfg_pl_val(Name, List) ->
case proplists:get_value(Name, List) of
undefined ->
error_logger:error_report([{error, app_cfg_missing},
{get_app_config, Name}]),
throw(app_cfg_missing);
{ok, Val} ->
{get_cfg_pl_val, Name}]);
Val ->
Val
end.