Wrap sctp_handler.erl into an OTP gen_server behavior

This commit is contained in:
Harald Welte 2011-01-22 20:53:50 +00:00
parent f62f0ed140
commit 789c8b14ac
2 changed files with 58 additions and 6 deletions

51
src/mgw_nat_usr.erl Normal file
View File

@ -0,0 +1,51 @@
% 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) ->
gen_server:start_link({local, ?MODULE}, ?MODULE, Params, []).
stop() ->
gen_server:cast(?MODULE, stop).
%% Callback functions of the OTP behavior
init(Params) ->
apply(sctp_handler, init, Params).
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}, LoopData) ->
NewL = sctp_handler:handle_sctp(LoopData, {sctp, Sock, Ip, Port, Data}),
{noreply, NewL}.

View File

@ -22,7 +22,7 @@
-module(sctp_handler).
-author("Harald Welte <laforge@gnumonks.org>").
-export([init/5]).
-export([init/5, handle_sctp/2]).
-include_lib("kernel/include/inet.hrl").
-include_lib("kernel/include/inet_sctp.hrl").
@ -52,7 +52,7 @@ init(MscLocalIP, MscLocalPort, MscRemoteIP, StpRemoteIP, StpRemotePort) ->
msc_remote_ip = MscRemoteIP,
stp_sock = StpSock, stp_remote_ip = StpRemoteIP,
stp_remote_port = StpRemotePort},
loop(L).
{ok, L}.
% initiate a connection to STP as a client
initiate_stp_connection(#loop_data{stp_sock = Sock, stp_remote_ip = IP, stp_remote_port = Port}, Opts) ->
@ -60,11 +60,12 @@ initiate_stp_connection(#loop_data{stp_sock = Sock, stp_remote_ip = IP, stp_remo
gen_sctp:connect(Sock, IP, Port, Opts ++ ?COMMON_SOCKOPTS).
% main loop function
loop(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port=MscRemotePort,
stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort}) ->
handle_sctp(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port=MscRemotePort,
stp_sock=StpSock, stp_remote_ip=StpRemoteIp, stp_remote_port=StpRemotePort},
Sctp) ->
io:format("Entering receive loop ~p~n", [L]),
io:format("======================================================================~n"),
receive
case Sctp of
% MSC connect or disconnect
{sctp, MscSock, MscRemoteIp, Port, {ANC, SAC}}
when is_record(SAC, sctp_assoc_change) ->
@ -120,7 +121,7 @@ loop(L = #loop_data{msc_sock=MscSock, msc_remote_ip=MscRemoteIp, msc_remote_port
io:format("OTHER ~p~n", [Other]),
NewL = L
end,
loop(NewL).
NewL.
try_mangle(L, From, Data) ->