aboutsummaryrefslogtreecommitdiffstats
path: root/src/mgw_nat_usr.erl
blob: 872bab15c8c15ed21857b01e94a93f38dfbc1d97 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
% Wrapper code, wrapping sctp_handler.erl into OTP gen_server

% (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_usr).
-author("Harald Welte <laforge@gnumonks.org>").

-behavior(gen_server).

-export([start_link/1, stop/0]).
-export([init/1, handle_cast/2, handle_info/2, terminate/2]).


start_link(Params) ->
	MscName = get_cfg_pl_val(msc_name, Params),
	gen_server:start_link({local, MscName}, ?MODULE, Params, []).

stop() ->
	gen_server:cast(?MODULE, stop).

%% Callback functions of the OTP behavior

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(),
	SctpHdlrArgs =	[MscLocalIp, MscLocalPort, MscRemoteIp,
			 StpRemoteIp, StpRemotePort, RewriteActMod],
	{ok, 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}.


terminate(_Reason, _LoopData) ->
	ok.

% callback for other events like incoming SCTP message
handle_info({sctp, Sock, Ip, Port, Data}, {InitParams, LoopData}) ->
	NewL = sctp_handler:handle_sctp(LoopData, {sctp, Sock, Ip, Port, Data}),
	{noreply, {InitParams, NewL}}.

% 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_cfg_pl_val, Name}]);
	    Val ->
		Val
	end.