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
diff --git a/src/sctp_core.erl b/src/sctp_core.erl
index f3a2bb9..2cd8b95 100644
--- a/src/sctp_core.erl
+++ b/src/sctp_core.erl
@@ -34,7 +34,8 @@
 -export([idle/2, associating/2, established/2]).
 
 behaviour_info(callbacks) ->
-	gen_fsm:behaviour_info(callbacks) ++ [{rx_sctp, 4}, {mtp_xfer, 2}, {state_change, 2}];
+	gen_fsm:behaviour_info(callbacks) ++ 
+	[{rx_sctp, 4}, {mtp_xfer, 2}, {state_change, 2}, {prim_up, 3}];
 behaviour_info(Other) ->
 	gen_fsm:behaviour_info(Other).
 
@@ -127,6 +128,16 @@
 	UserPid = LoopDat#sctp_state.user_pid,
 	UserPid ! Prim.
 
+prim_up_to_callback(Prim, State, LoopDat) ->
+	Module = LoopDat#sctp_state.module,
+	case Module:prim_up(Prim, State, LoopDat#sctp_state.ext_state) of
+		{ok, Prim, ExtNew} ->
+			send_prim_to_user(LoopDat, Prim);
+		{ignore, ExtNew} ->
+			ok
+	end,
+	LoopDat#sctp_state{ext_state = ExtNew}.
+
 
 handle_event(Event, State, LoopDat) ->
 	Module = LoopDat#sctp_state.module,
@@ -154,7 +165,8 @@
 					Spec = indication
 			end,
 			% primitive to the user
-			send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',Spec));
+			LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_ESTABLISH',Spec),
+						       State, LoopDat);
 		SacState == comm_lost ->
 			case State of
 				releasing ->
@@ -162,11 +174,12 @@
 				_ ->
 					Spec = indication
 			end,
-			send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',Spec)),
+			LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_RELEASE',Spec),
+							State, LoopDat),
 			case LoopDat#sctp_state.role of
 				active ->
 					NewState = associating,
-					reconnect_sctp(LoopDat);
+					reconnect_sctp(LoopDat2);
 				_ ->
 					NewState = idle
 			end;
@@ -177,10 +190,11 @@
 					reconnect_sctp(LoopDat);
 				_ ->
 					NewState = idle
-			end
+			end,
+			LoopDat2 = LoopDat
 	end,
 	inet:setopts(Socket, [{active, once}]),
-	next_state(State, NewState, LoopDat#sctp_state{sctp_assoc_id = AssocId});
+	next_state(State, NewState, LoopDat2#sctp_state{sctp_assoc_id = AssocId});
 
 handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
 	Module = LoopDat#sctp_state.module,
@@ -225,24 +239,34 @@
 
 
 idle(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = request}, LoopDat) ->
+	% M-SCTP_ESTABLISH.req from User
 	case LoopDat#sctp_state.role of
 		active ->
 			reconnect_sctp(LoopDat);
 		_ ->
 			ok
 	end,
-	next_state(idle, associating, LoopDat).
+	next_state(idle, associating, LoopDat);
+idle(Prim, LoopDat) when is_record(Prim, primitive) ->
+	LoopDat2 = prim_up_to_callback(Prim, idle, LoopDat),
+	next_state(idle, idle, LoopDat2).
 
 
 
 associating(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
 			spec_name = request}, LoopDat) ->
+	% M-SCTP_RELEASE.req from User
 	% directly send RELEASE.conf ?!?
-	next_state(associating, idle, LoopDat).
+	next_state(associating, idle, LoopDat);
+associating(Prim, LoopDat) when is_record(Prim, primitive) ->
+	LoopDat2 = prim_up_to_callback(Prim, associating, LoopDat),
+	next_state(associating, associating, LoopDat2).
+
 
 
 established(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
 			spec_name = request}, LoopDat) ->
+	% M-SCTP_RELEASE.req from User
 	next_state(established, releasing, LoopDat);
 established(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
 		       spec_name = request, parameters = Params}, LoopDat) ->
@@ -255,7 +279,10 @@
 	io:format("SCTP-TRANSFER.req~n",[]),
 	% somebody (typically callback module) requests us to send SCTP data
 	send_sctp_to_peer(LoopDat, Data, Stream, Ppid),
-	next_state(established, established, LoopDat).
+	next_state(established, established, LoopDat);
+established(Prim, LoopDat) when is_record(Prim, primitive) ->
+	LoopDat2 = prim_up_to_callback(Prim, established, LoopDat),
+	next_state(established, established, LoopDat2).
 
 next_state(State, NewState, LoopDat) when is_record(LoopDat, sctp_state) ->
 	Module = LoopDat#sctp_state.module,
diff --git a/src/sctp_m2pa.erl b/src/sctp_m2pa.erl
index d31f7de..c42c16a 100644
--- a/src/sctp_m2pa.erl
+++ b/src/sctp_m2pa.erl
@@ -27,7 +27,7 @@
 
 -export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
 
--export([rx_sctp/4, mtp_xfer/2, state_change/3]).
+-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
 
 -record(m2pa_state, {
 		last_bsn_received,
@@ -72,6 +72,11 @@
 % sctp_core callbacks
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
+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 = ?M2PA_PPID}, Data, State, LoopDat) ->
 	{ok, M2pa} = m2pa_codec:parse_msg(Data),
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).