SCCP: Make sure connection oriented messages end up with the user

The user initiating the connection should get all messages related to
that connection, not the supervisor ;)
diff --git a/src/sccp_scoc.erl b/src/sccp_scoc.erl
index 8b6afd3..9796cc9 100644
--- a/src/sccp_scoc.erl
+++ b/src/sccp_scoc.erl
@@ -142,10 +142,18 @@
 	Class = proplists:get_value(protocol_class, Params),
 	LoopDat1 = LoopDat#state{remote_reference = RemRef, class = Class,
 				 mtp3_label = mtp3_codec:invert_rout_lbl(Mtp3Label)},
-	% send N-CONNECT.ind to user
-	send_user(LoopDat1, osmo_util:make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
-	%#primitive{subsystem = 'N', gen_name = 'CONNECT', spec_name = indication}
-	{next_state, conn_pend_in, LoopDat1};
+	case LoopDat1#state.user_pid of
+		undefined ->
+			io:format("CR to unequipped subsystem!~n"),
+			RefParam = [{refusal_cause, ?SCCP_CAUSE_REF_UNEQUIPPED_USER}],
+			Prim = gen_co_sccp_prim(?SCCP_MSGT_CREF, RefParam, LoopDat1),
+			gen_fsm:send_event(LoopDat#state.scrc_pid, Prim),
+			{next_state, idle, LoopDat1};
+		_ ->
+			% send N-CONNECT.ind to user
+			send_user(LoopDat1, osmo_util:make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
+			{next_state, conn_pend_in, LoopDat1}
+	end;
 
 % RCOC-ROUTING_FAILURE.ind from SCRC
 idle(#primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
diff --git a/src/sccp_scrc.erl b/src/sccp_scrc.erl
index 53e6c08..6d92a99 100644
--- a/src/sccp_scrc.erl
+++ b/src/sccp_scrc.erl
@@ -30,7 +30,7 @@
 -record(scrc_state, {
 		scoc_conn_ets,
 		next_local_ref,
-		user_pid	% pid() of the user process
+		sup_pid	% pid() of the supervisor
 	}).
 % TODO: Integrate with proper SCCP routing / GTT implementation
 
@@ -49,13 +49,13 @@
 start_link(InitData) ->
 	% make sure to store the Pid of the caller in the scrc_state
 	gen_fsm:start_link({local, sccp_scrc}, sccp_scrc, 
-			   [{user_pid,self()}|InitData], [{debug, [trace]}]).
+			   [{sup_pid,self()}|InitData], [{debug, [trace]}]).
 
 % gen_fsm init callback, called by start_link()
 init(InitPropList) ->
 	io:format("SCRC Init PropList~p ~n", [InitPropList]),
-	UserPid = proplists:get_value(user_pid, InitPropList),
-	LoopData = #scrc_state{user_pid = UserPid, next_local_ref = 0},
+	UserPid = proplists:get_value(sup_pid, InitPropList),
+	LoopData = #scrc_state{sup_pid = UserPid, next_local_ref = 0},
 	TableRef = ets:new(scoc_by_ref, [set]),
 	put(scoc_by_ref, TableRef),
 	ok = ss7_links:bind_service(?MTP3_SERV_SCCP, "osmo_sccp"),
@@ -69,14 +69,14 @@
 	ok.
 
 % helper function to create new SCOC instance
-spawn_new_scoc(LoopDat) when is_record(LoopDat, scrc_state) ->
+spawn_new_scoc(LoopDat, UserPid) when is_record(LoopDat, scrc_state) ->
 	% create new SCOC instance
-	UserPid = LoopDat#scrc_state.user_pid,
 	% Compute the new local reference
 	LocalRef = LoopDat#scrc_state.next_local_ref + 1,
 	LoopDat1 = LoopDat#scrc_state{next_local_ref = LocalRef},
 	% generate proplist for SCRC initialization
 	ScocPropList = [{scrc_pid, self()}, {user_pid, UserPid}, {local_reference, LocalRef}],
+	% FIXME: we should rather ask the supervisor to start it on our behalf
 	{ok, ScocPid} = sccp_scoc:start_link(ScocPropList),
 	% insert SCOC instance in connection table
 	ConnTable = get(scoc_by_ref),
@@ -98,7 +98,7 @@
 		% special handling for CR message here in SCRC
 		#sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
 			% spawn a new SCOC instance/process
-			{LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
+			{LoopDat1, ScocPid} = spawn_new_scoc(LoopDat, UserPid),
 			% send a RCOC-CONNECTING.ind primitive to the new SCOC fsm
 			UserPrim = osmo_util:make_prim('RCOC','CONNECTION', indication, Msg#sccp_msg.parameters),
 			io:format("Sending ~p to ~p~n", [UserPrim, ScocPid]),
@@ -139,11 +139,13 @@
 
 % N-CONNECT.req from user: spawn new SCOC and deliver primitive to it
 idle(P = #primitive{subsystem = 'N', gen_name = 'CONNECT',
-		    spec_name = request}, LoopDat) ->
+		    spec_name = request, parameters = ParamsIn}, LoopDat) ->
+	UserPid = proplists:get_value(user_pid, ParamsIn),
+	ParamsOut = proplists:delete(user_pid, ParamsIn),
 	% Start new SCOC instance
-	{LoopDat1, ScocPid} = spawn_new_scoc(LoopDat),
+	{LoopDat1, ScocPid} = spawn_new_scoc(LoopDat, UserPid),
 	% Deliver primitive to new SCOC instance
-	gen_fsm:send_event(ScocPid, P),
+	gen_fsm:send_event(ScocPid, P#primitive{parameters = ParamsOut}),
 	{next_state, idle, LoopDat1};
 
 % N-UNITDATA.req from user (normally this is SCLC, but we don't have SCLC)