xua_asp_fsm: add support for SG mode in addition to existing ASP mode
diff --git a/src/sctp_m2ua.erl b/src/sctp_m2ua.erl
index 91e24d9..039f1bd 100644
--- a/src/sctp_m2ua.erl
+++ b/src/sctp_m2ua.erl
@@ -1,6 +1,6 @@
 % M2UA in accordance with RFC3331 (http://tools.ietf.org/html/rfc3331)
 
-% (C) 2011-2012 by Harald Welte <laforge@gnumonks.org>
+% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
 %
 % All Rights Reserved
 %
@@ -27,6 +27,8 @@
 -include("m2ua.hrl").
 -include("m3ua.hrl").
 
+-define(M2UA_STREAM_USER,	1).
+
 -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]).
@@ -41,9 +43,11 @@
 % gen_fsm callbacks
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-init(_InitOpts) ->
-	Fun = fixme, % FIXME
-	{ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
+init([Role]) ->
+	Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
+	AsPid = undefined, % FIXME
+	% we use sua_asp module, as m2ua has no difference here
+	{ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self(), Role], [{debug, [trace]}]),
 	{ok, #m2ua_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff, asp_pid=Asp}}.
 
 terminate(Reason, _State, _LoopDat) ->
@@ -64,9 +68,14 @@
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
+	% confirmation in case of active/connect mode
 	Asp = LoopDat#m2ua_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 = 'SCTP_ESTABLISH', spec_name = indication}, State, LoopDat) ->
+	% indication in case of passive/listen mode
+	Asp = LoopDat#m2ua_state.asp_pid,
+	{ignore, LoopDat};
 prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
 	Asp = LoopDat#m2ua_state.asp_pid,
 	gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
@@ -79,7 +88,7 @@
 % sctp_core indicates that we have received some data...
 rx_sctp(#sctp_sndrcvinfo{ppid = ?M2UA_PPID}, Data, State, LoopDat) ->
 	Asp = LoopDat#m2ua_state.asp_pid,
-	{ok, M2ua} = xua_codec:parse_msg(Data),
+	M2ua = xua_codec:parse_msg(Data),
 	% FIXME: check sequenc number linearity
 	case M2ua of
 		#xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
@@ -120,7 +129,7 @@
 			  msg_type = ?M2UA_MAUP_MSGT_DATA} ->
 			Mtp3 = proplists:get_value(?M2UA_P_M2UA_DATA1, M2ua#xua_msg.payload),
 			Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
-			{ignore, LoopDat};
+			{ok, Prim, LoopDat};
 		_ ->
 			% do something with link related msgs
 			io:format("M2UA Unknown message ~p in state ~p~n", [M2ua, State]),
@@ -128,13 +137,16 @@
 	end.
 
 % MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
+mtp_xfer(M2ua, LoopDat) when is_record(M2ua, xua_msg) ->
+	M2uaBin = xua_codec:encode_msg(M2ua),
+	tx_sctp(?M2UA_STREAM_USER, M2uaBin),
+	LoopDat;
+
 mtp_xfer(Mtp3, LoopDat) ->
 	M2ua = #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
 			 msg_type = ?M2UA_MAUP_MSGT_DATA,
 			 payload = {?M2UA_P_M2UA_DATA1, length(Mtp3), Mtp3}},
-	M2paBin = xua_codec:encode_msg(M2ua),
-	% FIXME tx_sctp(?M2UA_STREAM_USER, M2paBin),
-	LoopDat.
+	mtp_xfer(M2ua, LoopDat).
 
 state_change(_, established, LoopDat) ->
 	% emulate a 'start' from LSC
@@ -163,3 +175,7 @@
 	Param = {Stream, ?M2UA_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).
diff --git a/src/sctp_sua.erl b/src/sctp_sua.erl
index 2273c1e..2996b94 100644
--- a/src/sctp_sua.erl
+++ b/src/sctp_sua.erl
@@ -53,11 +53,11 @@
 % gen_fsm callbacks
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-init(_InitOpts) ->
+init([Role]) ->
 	% start SUA ASP
 	Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
 	AsPid = undefined,
-	{ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
+	{ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self(), Role], [{debug, [trace]}]),
 	{ok, #sua_state{asp_pid=Asp}}.
 
 terminate(Reason, _State, _LoopDat) ->
diff --git a/src/ss7_link_m2ua.erl b/src/ss7_link_m2ua.erl
index 494f042..3d93feb 100644
--- a/src/ss7_link_m2ua.erl
+++ b/src/ss7_link_m2ua.erl
@@ -42,24 +42,27 @@
 
 -export([start_link/1, init/1]).
 
--export([handle_cast/2]).
+-export([handle_cast/2, terminate/2]).
 
 -record(loop_dat, {
 	 m2ua_pid,
 	 link
 	}).
 
-start_link(Args) ->
-	gen_server:start_link(?MODULE, Args, [{debug, [trace]}]).
+start_link(Args = #sigtran_link{name=LinkName}) ->
+	Name = list_to_atom("ss7_link_m2ua_" ++ LinkName),
+	gen_server:start_link({local, Name}, ?MODULE, Args, [{debug, [trace]}]).
 
 init(L = #sigtran_link{type = m2ua, name = Name, linkset_name = LinksetName,
-		       sls = Sls, local = Local, remote = Remote}) ->
+		       sls = Sls, local = Local, remote = Remote, role = Role}) ->
 	#sigtran_peer{ip = LocalIp, port = LocalPort} = Local,
 	#sigtran_peer{ip = RemoteIp, port = RemotePort} = Remote,
 	% start the M2UA link to the SG
-	Opts = [{module, sctp_m2ua}, {module_args, []},
+	Opts = [{module, sctp_m2ua}, {module_args, [Role]},
+		{sctp_role, ss7_links:role2sctp_role(Role)},
 		{user_pid, self()}, {sctp_remote_ip, RemoteIp},
 		{sctp_remote_port, RemotePort}, {sctp_local_port, LocalPort},
+		{sctp_local_ip, LocalIp},
 		{user_fun, fun m2ua_tx_to_user/2}, {user_args, self()}],
 	{ok, M2uaPid} = sctp_core:start_link(Opts),
 	% FIXME: register this link with SCCP_SCRC
@@ -92,10 +95,7 @@
 	scrc_tx_to_mtp(P, L#loop_dat.m2ua_pid),
 	{noreply, L};
 % This is what we receive from m2ua_tx_to_user/2
-handle_cast(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, L) ->
-	io:format("~p: SCTP_ESTABLISH.ind -> ASP_UP.req~n", [?MODULE]),
-	gen_fsm:send_event(L#loop_dat.m2ua_pid, osmo_util:make_prim('M','ASP_UP',request)),
-	{noreply, L};
+
 handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_UP', spec_name = confirm}, L) ->
 	io:format("~p: ASP_UP.ind -> ASP_ACTIVE.req~n", [?MODULE]),
 	set_link_state(L#loop_dat.link, up),
diff --git a/src/xua_asp_fsm.erl b/src/xua_asp_fsm.erl
index 0f9b2a4..02f52cc 100644
--- a/src/xua_asp_fsm.erl
+++ b/src/xua_asp_fsm.erl
@@ -49,7 +49,7 @@
 -export([send_sctp_to_peer/2, send_prim_to_user/2]).
 
 % global exports
--export([get_state/1, start_link/6]).
+-export([get_state/1, start_link/7]).
 
 -export([behaviour_info/1]).
 
@@ -61,7 +61,7 @@
 
 -record(asp_state, {
 		module,
-		role,
+		role,	% asp, sg
 		t_ack,
 		ext_state,
 		user_fun,
@@ -70,14 +70,14 @@
 		sctp_pid
 	}).
 
-start_link(AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid) ->
-	gen_fsm:start_link(?MODULE, [AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid], [{debug, [trace]}]).
+start_link(AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role) ->
+	gen_fsm:start_link(?MODULE, [AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role], [{debug, [trace]}]).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 % gen_fsm callbacks
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-init([AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid]) ->
+init([AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role]) ->
 	{ok, ExtState} = Module:init(ModuleArgs),
 	AspState = #asp_state{module = Module,
 			      user_fun = UserFun,
@@ -85,7 +85,7 @@
 			      ext_state = ExtState,
 			      as_pid = AsPid,
 			      sctp_pid = SctpPid,
-			      role = asp},
+			      role = Role},
 	{ok, asp_down, AspState}.
 
 terminate(Reason, State, _LoopDat) ->
@@ -120,18 +120,26 @@
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
-		    spec_name = request, parameters = _Params}, LoopDat) ->
+		    spec_name = request, parameters = _Params},
+	 LoopDat = #asp_state{role=asp}) ->
 	% M-ASP_UP.req from user, generate message and send to remote peer
 	send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
 asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
 	send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
 
-asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
+asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK},
+	 LoopDat = #asp_state{role=asp}) ->
 	timer:cancel(LoopDat#asp_state.t_ack),
 	% transition into ASP_INACTIVE
 	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
 	next_state(asp_inactive, LoopDat);
 
+asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP},
+	 LoopDat = #asp_state{role=sg}) ->
+	% transition into ASP_INACTIVE
+	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',inidication)),
+	send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK, []);
+
 asp_down(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
 	{State, LDnew} = Module:asp_down(WhateverElse, ExtState, LoopDat),
 	next_state(State, LDnew).
@@ -142,7 +150,8 @@
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
-			spec_name = request, parameters = Params}, LoopDat) ->
+			spec_name = request, parameters = Params},
+	     LoopDat = #asp_state{role=asp}) ->
 	% M-ASP_ACTIVE.req from user, generate message and send to remote peer
 	send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
 			   Params);
@@ -151,27 +160,46 @@
 	send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
 
 asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
-		      spec_name = request, parameters = _Params}, LoopDat) ->
+		      spec_name = request, parameters = _Params},
+	     LoopDat = #asp_state{role=asp}) ->
 	% M-ASP_DOWN.req from user, generate message and send to remote peer
 	send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
 
 asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
 	send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
 
-asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
+asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK},
+	     LoopDat = #asp_state{role=asp}) ->
 	timer:cancel(LoopDat#asp_state.t_ack),
 	% transition into ASP_ACTIVE
 	% signal this to the user
 	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
 	next_state(asp_active, LoopDat);
 
-asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
+asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK},
+	     LoopDat = #asp_state{role=asp}) ->
 	timer:cancel(LoopDat#asp_state.t_ack),
 	% transition into ASP_DOWN
 	% signal this to the user
 	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
 	next_state(asp_down, LoopDat);
 
+
+asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC},
+	     LoopDat = #asp_state{role=sg}) ->
+	% transition into ASP_ACTIVE
+	% signal this to the user
+	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',indication)),
+	send_msg(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK, []);
+
+asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN},
+	     LoopDat = #asp_state{role=asp}) ->
+	% transition into ASP_DOWN
+	% signal this to the user
+	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',indication)),
+	send_msg(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK, []);
+
+
 asp_inactive(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
 	{State, LDnew} = Module:asp_inactive(WhateverElse, ExtState, LoopDat),
 	next_state(State, LDnew).
@@ -181,14 +209,16 @@
 % STATE "asp_active"
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
+asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK},
+	   LoopDat = #asp_state{role=asp}) ->
 	timer:cancel(LoopDat#asp_state.t_ack),
 	% transition into ASP_DOWN
 	% signal this to the user
 	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
 	next_state(asp_down, LoopDat);
 
-asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
+asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK},
+	   LoopDat = #asp_state{role=asp}) ->
 	timer:cancel(LoopDat#asp_state.t_ack),
 	% transition into ASP_INACTIVE
 	% signal this to the user
@@ -196,7 +226,8 @@
 	next_state(asp_inactive, LoopDat);
 
 asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
-		      spec_name = request, parameters = _Params}, LoopDat) ->
+		      spec_name = request, parameters = _Params},
+	   LoopDat = #asp_state{role=asp}) ->
 	% M-ASP_DOWN.req from user, generate message and send to remote peer
 	send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
 
@@ -204,13 +235,29 @@
 	send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
 
 asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
-		      spec_name = request, parameters = _Params}, LoopDat) ->
+		      spec_name = request, parameters = _Params},
+	   LoopDat = #asp_state{role=asp}) ->
 	% M-ASP_INACTIVE.req from user, generate message and send to remote peer
 	send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
 
 asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
 	send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
 
+asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA},
+	   LoopDat = #asp_state{role=sg}) ->
+	% transition into ASP_INACTIVE
+	% signal this to user
+	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',indication)),
+	send_msg(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK, []);
+
+asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN},
+	   LoopDat = #asp_state{role=sg}) ->
+	% transition into ASP_INACTIVE
+	% signal this to user
+	send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',indication)),
+	send_msg(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK, []);
+
+
 asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
 		      spec_name = request, parameters = Params}, LoopDat) ->
 	% MTP-TRANSFER.req from user app: Send message to remote peer
@@ -249,6 +296,12 @@
 				 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
 	next_state(State, LoopDat#asp_state{t_ack = Tack}).
 
+send_msg(LoopDat, State, MsgClass, MsgType, Params) ->
+	Module = LoopDat#asp_state.module,
+	% generate and send the respective message
+	Msg = Module:gen_xua_msg(MsgClass, MsgType, Params),
+	send_sctp_to_peer(LoopDat, Msg),
+	next_state(State, LoopDat).
 
 send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, asp_state),
 				      is_record(Prim, primitive) ->