complete SCCP routing code

we now use ss7_links in order to determine which point codes are local
or not, and we use the routing table to determine the signalling link.

local-out routing form N-UNITDATA.req to the actual MTP3 on the correct
signalling link is now working.
diff --git a/src/sccp_routing.erl b/src/sccp_routing.erl
index bf5ae21..eda4072 100644
--- a/src/sccp_routing.erl
+++ b/src/sccp_routing.erl
@@ -24,17 +24,10 @@
 -include_lib("osmo_ss7/include/sccp.hrl").
 -include_lib("osmo_ss7/include/mtp3.hrl").
 
--export([route_mtp3_sccp_in/1, route_local_out/1]).
+-export([route_mtp3_sccp_in/1, route_local_out/1, select_opc/2]).
 
-pointcode_is_local(Pc) ->
-	% FIXME: use SCRC routing information
-	LocalPc = osmo_util:pointcode2int(itu, {1,2,4}),
-	case Pc of
-		LocalPc ->
-			true;
-		_ ->
-			false
-	end.
+pointcode_is_local(Pc) when is_integer(Pc) ->
+	ss7_links:is_pc_local(Pc).
 
 % local helper function
 msg_return_or_cr_refusal(SccpMsg, RetCause, RefCause) ->
@@ -94,6 +87,30 @@
 	end,
 	route_local_out_action(Action, SccpMsg, CalledParty).
 
+% select Originating Point Code for given (local_out) SCCP Msg
+select_opc(SccpMsg, LsName) when is_record(SccpMsg, sccp_msg) ->
+	% first try to find the Calling Party as specified by user
+	case proplists:get_value(calling_party_addr,
+				 SccpMsg#sccp_msg.parameters) of
+	    undefined ->
+		% no calling party: auto selection
+		select_opc_auto(SccpMsg, LsName);
+	    CallingParty ->
+		case CallingParty#sccp_addr.point_code of
+		    % calling party has no point code: auto selection
+		    undefined ->
+			select_opc_auto(SccpMsg, LsName);
+		    Opc ->
+			% calling party has point code: use it
+			Opc
+		end
+	end.
+
+select_opc_auto(SccpMsg, LsName) when is_record(SccpMsg, sccp_msg) ->
+	% use SS7 link management to determine Opc
+	ss7_links:get_opc_for_linkset(LsName).
+
+
 % Acccording to 2.3.2 Action (1)
 route_local_out_action(1, SccpMsg, CalledParty) ->
 	#sccp_addr{global_title = Gt, ssn = Ssn, point_code = Pc} = CalledParty,
@@ -116,7 +133,8 @@
 		% primitive is invoked unless the compatibility test returns
 		% the message to SCLC or unless the message is discarded by the
 		% traffic limitation mechanism;
-		{remote, SccpMsg}
+		LsName = ss7_routes:route_dpc(Pc),
+		{remote, SccpMsg, LsName}
 	end;
 
 % Acccording to 2.3.2 Action (2)
@@ -140,7 +158,8 @@
 			% compatibility test returns the message to SCLC or
 			% unless the message is discarded by the traffic
 			% limitation mechanism
-			{remote, SccpMsg}
+			LsName = ss7_routes:route_dpc(Dpc),
+			{remote, SccpMsg, LsName}
 		end
 	end;
 
@@ -159,7 +178,8 @@
 		% primitive is invoked unless the compatibility test returns
 		% the message to SCLC or unless the message is discarded by the
 		% traffic limitation mechanism;
-		{remote, SccpMsg}
+		LsName = ss7_routes:route_dpc(Pc),
+		{remote, SccpMsg, LsName}
 	end;
 
 % Acccording to 2.3.2 Action (4)
@@ -208,6 +228,7 @@
 	% FIXME: handle UDTS/XUDTS/LUDTS messages (RI=0 check) of C.1/Q.714 (1/12)
 	% FIXME: handle translation already performed == yes) case of C.1/Q.714 (1/12)
 	route_main(SccpMsg),
+	%LsName = ss7_routes:route_dpc(),
 	{remote, SccpMsg}.
 
 
diff --git a/src/sccp_scrc.erl b/src/sccp_scrc.erl
index 7377d81..2765da0 100644
--- a/src/sccp_scrc.erl
+++ b/src/sccp_scrc.erl
@@ -149,33 +149,34 @@
 idle(P= #primitive{subsystem = 'N', gen_name = 'UNITDATA',
 		   spec_name = request, parameters = Params}, LoopDat) ->
 	% User needs to specify: Protocol Class, Called Party, Calling Party, Data
-	% FIXME: implement XUDT / LUDT support
-	% encode the actual SCCP message
-	EncMsg = sccp_codec:encode_sccp_msgt(?SCCP_MSGT_UDT, Params),
-	% generate a MTP-TRANSFER.req primitive to the lower layer
-	send_mtp_transfer_down(LoopDat, EncMsg),
-	{next_state, idle, LoopDat};
+	SccpMsg = #sccp_msg{msg_type = ?SCCP_MSGT_UDT, parameters = Params},
+	case sccp_routing:route_local_out(SccpMsg) of
+		{remote, SccpMsg2, LsName} ->
+			% FIXME: get to MTP-TRANSFER.req
+			{ok, M3} = create_mtp3_out(SccpMsg2, LsName),
+			% generate a MTP-TRANSFER.req primitive to the lower layer
+			send_mtp_transfer_down(LoopDat, M3),
+			LoopDat1 = LoopDat;
+		{local, SccpMsg2, UserPid} ->
+			LoopDat1 = deliver_to_scoc_sclc(LoopDat, SccpMsg2, UserPid)
+	end,
+	{next_state, idle, LoopDat1};
+
 % MTP-TRANSFER.ind from lower layer is passed into SCRC
 idle(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
 		spec_name = indication, parameters = Params}, LoopDat) ->
 	case sccp_routing:route_mtp3_sccp_in(Params) of
-		{remote, SccpMsg} ->
-			% routing has taken care of it 
+		{remote, SccpMsg2, LsName} ->
+			{ok, M3} = create_mtp3_out(SccpMsg2, LsName),
+			% generate a MTP-TRANSFER.req primitive to the lower layer
+			send_mtp_transfer_down(LoopDat, M3),
 			LoopDat1 = LoopDat;
 		{local, SccpMsg, UserPid} ->
 			LoopDat1 = deliver_to_scoc_sclc(LoopDat, SccpMsg, UserPid)
 	end,
 	{next_state, idle, LoopDat1};
 idle({sclc_scrc_connless_msg, SccpMsg}, LoopDat) ->
-	case sccp_routing:route_local_out(SccpMsg) of
-		{remote, SccpMsg2} ->
-			% FIXME: get to MTP-TRANSFER.req
-			LoopDat1 = LoopDat;
-		{error, _} ->
-			LoopDat1 = LoopDat;
-		{local, SccpMsg2, UserPid} ->
-			LoopDat1 = deliver_to_scoc_sclc(LoopDat, SccpMsg2, UserPid)
-	end,
+	% FIXME: see above, N-UNITDATA.req from user
 	{next_state, idle, LoopDat};
 % connection oriented messages like N-DATA.req from user
 idle(#primitive{subsystem = 'OCRC', gen_name = 'CONNECTION-MSG',
@@ -204,11 +205,33 @@
 	send_mtp_transfer_down(LoopDat, EncMsg),
 	{next_state, idle, LoopDat}.
 
-send_mtp_transfer_down(LoopDat, EncMsg) ->
-	Rlbl = #mtp3_routing_label{sig_link_sel = 0, origin_pc = 123, dest_pc = 456},
-	Mtp3 = #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL,
-			 service_ind = ?MTP3_SERV_SCCP,
-			 routing_label = Rlbl, payload = EncMsg},
-	MtpPrim = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
-			     spec_name = request, parameters = Mtp3},
+send_mtp_transfer_down(LoopDat, Mtp3) when is_record(Mtp3, mtp3_msg) ->
 	ss7_links:mtp3_tx(Mtp3).
+
+create_mtp3_out(SccpMsg, LsName) when is_record(SccpMsg, sccp_msg) ->
+	CalledParty = proplists:get_value(called_party_addr,
+					  SccpMsg#sccp_msg.parameters),
+	% we _have_ to have a destination point code here
+	Dpc = CalledParty#sccp_addr.point_code,
+	case Dpc of
+	    undefined ->
+		{error, dpc_undefined};
+	    _ ->
+		Opc = sccp_routing:select_opc(SccpMsg, LsName),
+		case Opc of
+		    undefined ->
+			{error, opc_undefined};
+		    _ ->
+			% FIXME: implement XUDT / LUDT support
+			SccpEnc = sccp_codec:encode_sccp_msg(SccpMsg),
+			% FIXME: select sls at random 
+			M3R = #mtp3_routing_label{sig_link_sel = 0,
+				  origin_pc = Opc,
+				  dest_pc = Dpc},
+			M3 = #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL,
+				       service_ind = ?MTP3_SERV_SCCP,
+				       routing_label = M3R,
+				       payload = SccpEnc},
+			{ok, M3}
+		end
+	end.