summaryrefslogtreecommitdiffstats
path: root/src/sctp_sua.erl
diff options
context:
space:
mode:
authorHarald Welte <laforge@gnumonks.org>2012-01-17 10:12:34 +0100
committerHarald Welte <laforge@gnumonks.org>2012-01-17 10:12:34 +0100
commit91b7965efbdeb47e56ac506d299a6904fb50bbf0 (patch)
treee1b666fe0823a7eec08d16e02c8701f3b8ffa7fc /src/sctp_sua.erl
parent475ccdbf95177f600775a477fee3e6a84a091b2d (diff)
sctp_core: Make sure to pass all primitives in all states to callback
the callback (sctp_sua/sctp_m2pa) can then either act on it by itself or forward the message to the user
Diffstat (limited to 'src/sctp_sua.erl')
-rw-r--r--src/sctp_sua.erl132
1 files changed, 132 insertions, 0 deletions
diff --git a/src/sctp_sua.erl b/src/sctp_sua.erl
new file mode 100644
index 0000000..d64eedc
--- /dev/null
+++ b/src/sctp_sua.erl
@@ -0,0 +1,132 @@
+% SUA behaviour call-back for sctp_core
+
+% (C) 2011-2012 by Harald Welte <laforge@gnumonks.org>
+%
+% 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(sctp_sua).
+-author('Harald Welte <laforge@gnumonks.org>').
+-behaviour(sctp_core).
+
+-include_lib("kernel/include/inet_sctp.hrl").
+-include("osmo_util.hrl").
+-include("sua.hrl").
+-include("m3ua.hrl").
+
+-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
+
+-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
+
+-record(sua_state, {
+ asp_pid
+ }).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% gen_fsm callbacks
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+init(_InitOpts) ->
+ % start SUA ASP
+ Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
+ {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
+ {ok, #sua_state{asp_pid=Asp}}.
+
+terminate(Reason, _State, _LoopDat) ->
+ io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
+ ok.
+
+code_change(_OldVsn, _State, LoopDat, _Extra) ->
+ {ok, LoopDat}.
+
+handle_event(_Event, State, LoopDat) ->
+ {next_state, State, LoopDat}.
+
+handle_info(_Info, State, LoopDat) ->
+ {next_state, State, LoopDat}.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% sctp_core callbacks
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
+ Asp = LoopDat#sua_state.asp_pid,
+ gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
+ {ignore, LoopDat};
+prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
+ Asp = LoopDat#sua_state.asp_pid,
+ gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
+ {ignore, LoopDat};
+prim_up(Prim, State, LoopDat) ->
+ % default: forward all primitives to the user
+ {ok, Prim, LoopDat}.
+
+
+% sctp_core indicates that ew have received some data...
+rx_sctp(#sctp_sndrcvinfo{ppid = ?SUA_PPID}, Data, State, LoopDat) ->
+ Asp = LoopDat#sua_state.asp_pid,
+ Sua = sua_codec:parse_msg(Data),
+ case Sua of
+ #sua_msg{msg_class = ?M3UA_MSGC_MGMT,
+ msg_type = ?M3UA_MSGT_MGMT_NTFY} ->
+ Prim = osmo_util:make_prim('M','NOTIFY',indication,Sua),
+ {ok, Prim, LoopDat};
+ #sua_msg{msg_class = ?M3UA_MSGC_MGMT,
+ msg_type = ?M3UA_MSGT_MGMT_ERR} ->
+ Prim = osmo_util:make_prim('M','ERROR',indication,Sua),
+ {ok, Prim, LoopDat};
+ #sua_msg{msg_class = ?M3UA_MSGC_SSNM} ->
+ {ignore, LoopDat};
+ #sua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
+ gen_fsm:send_event(Asp, Sua),
+ {ignore, LoopDat};
+ #sua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
+ gen_fsm:send_event(Asp, Sua),
+ {ignore, LoopDat};
+ _ ->
+ % do something with link related msgs
+ io:format("SUA Unknown message ~p in state ~p~n", [Sua, State]),
+ {ignore, State, LoopDat}
+ end.
+
+% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
+mtp_xfer(Sua, LoopDat) when is_record(Sua, sua_msg) ->
+ SuaBin = sua_codec:encode_msg(Sua),
+ tx_sctp(1, SuaBin),
+ LoopDat.
+
+state_change(_, established, LoopDat) ->
+ % emulate a 'start' from LSC
+ %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, start),
+ LoopDat;
+state_change(established, _, LoopDat) ->
+ %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, link_failure),
+ LoopDat;
+state_change(_, _, LoopDat) ->
+ LoopDat.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% helper functions
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
+ Param = {Stream, ?SUA_PPID, Payload},
+ % sent to 'ourselves' (behaviour master module)
+ gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
+
+% callback fun for ASP FMS
+asp_prim_to_user(Prim, [SctpPid]) ->
+ gen_fsm:send_event(SctpPid, Prim).