M2PA: implement RC 'fiso_msu_accepted' flag

This flag prevents the accepting of FISU or MSU inside RC, ensuring that
those events cannot enter LSC/IAC during times where they are invalid.
diff --git a/src/m3ua_asp.erl b/src/m3ua_asp.erl
new file mode 100644
index 0000000..c459d4a
--- /dev/null
+++ b/src/m3ua_asp.erl
@@ -0,0 +1,97 @@
+% M3UA ASP xua_asp_fsm callback
+
+% (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(m3ua_asp).
+-author('Harald Welte <laforge@gnumonks.org>').
+-behaviour(xua_asp_fsm).
+
+-include("osmo_util.hrl").
+-include("m3ua.hrl").
+
+-export([init/1]).
+
+-export([gen_xua_msg/3, asp_down/3, asp_inactive/3, asp_active/3]).
+
+init([]) ->
+	{ok, we_have_no_state}.
+
+gen_xua_msg(MsgClass, MsgType, Params) ->
+	#m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params}.
+
+asp_down(#m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+	 LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
+	% convert from M3UA to xua_msg and call into master module
+	xua_asp_fsm:asp_down({xua_msg, MsgClass, MsgType}, Mld);
+asp_down(M3uaMsg, LoopDat, Mld) when is_record(M3uaMsg, m3ua_msg) ->
+	rx_m3ua(M3uaMsg, asp_down, Mld).
+
+asp_inactive(#m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+	     LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
+	% convert from M3UA to xua_msg and call into master module
+	xua_asp_fsm:asp_inactive({xua_msg, MsgClass, MsgType}, Mld);
+asp_inactive(M3uaMsg, LoopDat, Mld) when is_record(M3uaMsg, m3ua_msg) ->
+	rx_m3ua(M3uaMsg, asp_inactive, Mld).
+
+asp_active(#m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+	   LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
+	% convert from M3UA to xua_msg and call into master module
+	xua_asp_fsm:asp_active({xua_msg, MsgClass, MsgType}, Mld);
+asp_active(M3uaMsg, LoopDat, Mld) when is_record(M3uaMsg, m3ua_msg) ->
+	rx_m3ua(M3uaMsg, asp_active, Mld).
+
+
+
+
+
+rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
+			msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
+	xua_asp_fsm:send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
+	{next_state, State, LoopDat};
+
+rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
+			msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
+	% Send BEAT_ACK using the same payload as the BEAT msg
+	xua_asp_fsm:send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
+	{next_state, State, LoopDat};
+
+rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
+			msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
+	xua_asp_fsm:send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
+	{next_state, State, LoopDat};
+
+rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
+		        msg_type = MsgType, payload = Params}, State, LoopDat) ->
+	% transform to classic MTP primitive and send up to the user
+	Mtp = map_ssnm_to_mtp_prim(MsgType),
+	xua_asp_fsm:send_prim_to_user(LoopDat, Mtp),
+	{next_state, State, LoopDat};
+
+rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
+	io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
+	{next_state, State, LoopDat}.
+
+% Transform the M3UA SSNM messages into classic MTP primitives
+map_ssnm_to_mtp_prim(MsgType) ->
+	Mtp = #primitive{subsystem = 'MTP', spec_name = indication},
+	case MsgType of
+	    ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
+	    ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
+	    ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
+	    ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
+	end.
diff --git a/src/mtp2_iac.erl b/src/mtp2_iac.erl
index 3bb9762..1b756b7 100644
--- a/src/mtp2_iac.erl
+++ b/src/mtp2_iac.erl
@@ -298,10 +298,6 @@
 			send_to_lsc(alignment_complete, LoopDat),
 			fig9_4(LoopDat)
 	end;
-proving(fisu_msu_received, LoopDat) ->
-	% ignore FISU/MSU in this state, as some implementations
-	% (notably yate) seem to send it in violation of the spec
-	{next_state, proving, LoopDat};
 proving(abort_proving, LoopDat) ->
 	% Cp := Cp + 1
 	Cp = LoopDat#iac_state.cp,
diff --git a/src/mtp2_lsc.erl b/src/mtp2_lsc.erl
index 3cdf59a..1acbc80 100644
--- a/src/mtp2_lsc.erl
+++ b/src/mtp2_lsc.erl
@@ -40,6 +40,7 @@
 		l3_pid,
 		poc_pid,
 		txc_pid,
+		rc_pid,
 		local_proc_out,
 		proc_out,
 		emergency
@@ -51,7 +52,7 @@
 % gen_fsm callbacks
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-init([Aerm, Txc, L3, Poc]) ->
+init([Aerm, Rc, Txc, L3, Poc]) ->
 	{ok, Iac} = gen_fsm:start_link(mtp2_iac, [self(), Aerm, Txc], [{debug, [trace]}]),
 	LscState = #lsc_state{t1_timeout = ?M2PA_T1_DEF,
 			      iac_pid = Iac,
@@ -59,6 +60,7 @@
 			      l3_pid = L3,
 			      poc_pid = L3,
 			      txc_pid = Txc,
+			      rc_pid = Rc,
 		      	      local_proc_out = 0,
 		      	      proc_out = 0,
 		      	      emergency = 0},
@@ -168,11 +170,11 @@
 		1 ->
 			send_to(poc, local_processor_outage, LoopDat),
 			send_to(txc, si_po, LoopDat),
-			send_to(rc, reject_msu_fiso, LoopDat),
+			send_to(rc, reject_msu_fisu, LoopDat),
 			NextState = aligned_not_ready;
 		_ ->
 			send_to(txc, fisu, LoopDat),
-			send_to(rc, accept_msu_fiso, LoopDat),
+			send_to(rc, accept_msu_fisu, LoopDat),
 			NextState = aligned_ready
 	end,
 	{next_state, NextState, LoopDat#lsc_state{t1=T1}};
@@ -247,7 +249,7 @@
 					What == level3_failure ->
 	send_to(poc, local_processor_outage, LoopDat),
 	send_to(txc, si_po, LoopDat),
-	send_to(rc, reject_msu_fiso, LoopDat),
+	send_to(rc, reject_msu_fisu, LoopDat),
 	{next_state, aligned_not_ready, LoopDat}.
 
 
@@ -407,6 +409,8 @@
 	Txc ! {lsc_txc, What};
 send_to(iac, What, #lsc_state{iac_pid = Iac}) ->
 	gen_fsm:send_event(Iac, What);
+send_to(rc, What, #lsc_state{rc_pid = Rc}) ->
+	Rc ! {lsc_rc, What};
 send_to(Who, What, _LoopDat) ->
 	io:format("Not sending LSC -> ~p: ~p~n", [Who, What]).
 
diff --git a/src/sctp_m2pa.erl b/src/sctp_m2pa.erl
index 3979ad4..fdadd36 100644
--- a/src/sctp_m2pa.erl
+++ b/src/sctp_m2pa.erl
@@ -33,7 +33,8 @@
 		last_bsn_received,
 		last_fsn_sent,
 		lsc_pid,
-		iac_pid
+		iac_pid,
+		msu_fisu_accepted
 	}).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -42,11 +43,12 @@
 
 init(_InitOpts) ->
 	% start MTP2 IAC FSM pointing LSC, AERM and TXC to us
-	{ok, Lsc} = gen_fsm:start_link(mtp2_lsc, [self(), self(), self(),self()], [{debug, [trace]}]),
+	{ok, Lsc} = gen_fsm:start_link(mtp2_lsc, [self(), self(), self(), self(),self()], [{debug, [trace]}]),
 	{ok, Iac} = gen_fsm:sync_send_event(Lsc, get_iac_pid),
 	gen_fsm:send_event(Lsc, power_on),
 	{ok, #m2pa_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff,
-			 lsc_pid=Lsc, iac_pid=Iac}}.
+			 lsc_pid=Lsc, iac_pid=Iac,
+		 	 msu_fisu_accepted = 0}}.
 
 terminate(Reason, _State, _LoopDat) ->
 	io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
@@ -61,6 +63,10 @@
 handle_info({lsc_txc, What}, State, LoopDat) when
 			What == start; What == retrieval_request_and_fsnc ->
 	{next_state, State, LoopDat};
+handle_info({lsc_rc, accept_msu_fisu}, State, LoopDat) ->
+	{next_state, State, LoopDat#m2pa_state{msu_fisu_accepted = 1}};
+handle_info({lsc_rc, reject_msu_fisu}, State, LoopDat) ->
+	{next_state, State, LoopDat#m2pa_state{msu_fisu_accepted = 0}};
 handle_info({Who, What}, established, LoopDat) when Who == iac_txc; Who == lsc_txc ->
 	Ls = iac_to_ls(What),
 	send_linkstate(Ls, LoopDat),
@@ -86,15 +92,21 @@
 		#m2pa_msg{msg_class = ?M2PA_CLASS_M2PA,
 			  msg_type = ?M2PA_TYPE_USER} ->
 			Mtp3 = M2pa#m2pa_msg.mtp3,
-			LoopDat2 = LoopDat#m2pa_state{last_bsn_received = FsnRecv},
-			case Mtp3 of
-				undefined ->
-					ok;
+			case LoopDat#m2pa_state.msu_fisu_accepted of
+				1 ->
+					LoopDat2 = LoopDat#m2pa_state{last_bsn_received = FsnRecv},
+					case Mtp3 of
+						undefined ->
+							ok;
+						_ ->
+							send_userdata_ack(LoopDat2)
+					end,
+					gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, fisu_msu_received),
+					Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
+					{ok, Prim, LoopDat2};
 				_ ->
-					send_userdata_ack(LoopDat2)
-			end,
-			Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
-			{ok, Prim, LoopDat2};
+					{ignore, LoopDat}
+			end;
 		#m2pa_msg{msg_type = ?M2PA_TYPE_LINK} ->
 			handle_linkstate(M2pa, LoopDat),
 			{ignore, LoopDat};
@@ -139,7 +151,12 @@
 	Linkstate = proplists:get_value(link_state, M2pa#m2pa_msg.parameters),
 	LsMtp2 = ls_to_iac(Linkstate),
 	if LsMtp2 == fisu ->
-		gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, fisu_msu_received);
+		case LoopDat#m2pa_state.msu_fisu_accepted of
+			1 ->
+				gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid,
+						   fisu_msu_received);
+			0 -> ok
+		end;
 	   LsMtp2 == si_po ->
 		gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, LsMtp2);
 	   LsMtp2 == si_n; LsMtp2 == si_e; LsMtp2 == si_o; LsMtp2 == si_os ->