blob: 6b1a140c5a77efd31f29ddfd188e75f823d6b659 [file] [log] [blame]
Harald Weltea2ac6832011-10-09 14:32:30 +02001% SCCP routing code
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
19
20-module(sccp_routing).
21-author('Harald Welte <laforge@gnumonks.org>').
22
23-include_lib("osmo_ss7/include/osmo_util.hrl").
24-include_lib("osmo_ss7/include/sccp.hrl").
25-include_lib("osmo_ss7/include/mtp3.hrl").
26
Harald Welteab61a4e2011-10-12 17:19:45 +020027-export([route_mtp3_sccp_in/1, route_local_out/1, select_opc/2]).
Harald Weltea2ac6832011-10-09 14:32:30 +020028
Harald Welteb80119c2011-12-10 19:21:58 +010029pointcode_is_local(Pc) ->
30 PcInt = osmo_util:pointcode2int(Pc),
31 ss7_links:is_pc_local(PcInt).
Harald Weltea2ac6832011-10-09 14:32:30 +020032
33% local helper function
34msg_return_or_cr_refusal(SccpMsg, RetCause, RefCause) ->
35 case sccp_codec:is_connectionless(SccpMsg) of
Harald Welte8c9d4e72011-10-10 12:31:09 +020036 true ->
Harald Weltea2ac6832011-10-09 14:32:30 +020037 % if CL -> message return procedure
38 message_return(SccpMsg, RetCause);
Harald Welte8c9d4e72011-10-10 12:31:09 +020039 false ->
Harald Weltea2ac6832011-10-09 14:32:30 +020040 % if CR -> connection refusal
41 connection_refusal(SccpMsg, RefCause)
Harald Welte8c9d4e72011-10-10 12:31:09 +020042 end,
43 {error, routing}.
Harald Weltea2ac6832011-10-09 14:32:30 +020044
45% local outgoing CL or CR message
46route_local_out(SccpMsg) when is_record(SccpMsg, sccp_msg) ->
47 CalledParty = proplists:get_value(called_party_addr, SccpMsg#sccp_msg.parameters),
48 #sccp_addr{global_title = Gt, ssn = Ssn, point_code = Pc} = CalledParty,
49 if
50 (Gt == undefined) and ((Ssn == undefined) or (Ssn == 0)) ->
51 % left-most colunm of Table 1/Q714 -> Action four
52 Action = 4;
53 (Gt /= undefined) and ((Ssn == undefined) or (Ssn == 0)) ->
54 % second (from left) column of Table 1/Q.714
55 if (Pc == undefined) ->
56 Action = 2;
57 true ->
58 case pointcode_is_local(Pc) of
59 true ->
60 Action = 2;
61 false ->
62 Action = 3
63 end
64 end;
65 (Gt == undefined) and (Ssn /= undefined) ->
66 % third (from left) column of Table 1/Q.714
67 if (Pc == undefined) ->
68 Action = 4;
69 true ->
70 Action = 1
71 end;
72 (Gt /= undefined) and (Ssn /= undefined) ->
73 % last (from left) column of Table 1/Q.714
74 if (Pc == undefined) ->
75 Action = 2;
76 true ->
77 if CalledParty#sccp_addr.route_on_ssn ->
78 Action = 1;
79 true ->
80 case pointcode_is_local(Pc) of
81 true ->
82 Action = 2;
83 false ->
84 Action = 3
85 end
86 end
87 end
88 end,
89 route_local_out_action(Action, SccpMsg, CalledParty).
90
Harald Welteab61a4e2011-10-12 17:19:45 +020091% select Originating Point Code for given (local_out) SCCP Msg
92select_opc(SccpMsg, LsName) when is_record(SccpMsg, sccp_msg) ->
93 % first try to find the Calling Party as specified by user
94 case proplists:get_value(calling_party_addr,
95 SccpMsg#sccp_msg.parameters) of
96 undefined ->
97 % no calling party: auto selection
98 select_opc_auto(SccpMsg, LsName);
99 CallingParty ->
100 case CallingParty#sccp_addr.point_code of
101 % calling party has no point code: auto selection
102 undefined ->
103 select_opc_auto(SccpMsg, LsName);
104 Opc ->
105 % calling party has point code: use it
106 Opc
107 end
108 end.
109
110select_opc_auto(SccpMsg, LsName) when is_record(SccpMsg, sccp_msg) ->
111 % use SS7 link management to determine Opc
112 ss7_links:get_opc_for_linkset(LsName).
113
114
Harald Weltea2ac6832011-10-09 14:32:30 +0200115% Acccording to 2.3.2 Action (1)
116route_local_out_action(1, SccpMsg, CalledParty) ->
117 #sccp_addr{global_title = Gt, ssn = Ssn, point_code = Pc} = CalledParty,
118 case pointcode_is_local(Pc) of
119 true ->
120 % c) procedures 2.3.1, item 2) are folloed
Harald Welte09145642011-10-10 20:44:10 +0200121 case sccp_user:pid_for_ssn(Ssn, Pc) of
122 {ok, UserPid} ->
Harald Weltea2ac6832011-10-09 14:32:30 +0200123 % pass to either SCOC or SCLC
Harald Welte09145642011-10-10 20:44:10 +0200124 {local, SccpMsg, UserPid};
125 {error, _Error} ->
Harald Weltea2ac6832011-10-09 14:32:30 +0200126 % message return / connection refusal
127 msg_return_or_cr_refusal(SccpMsg,
128 ?SCCP_CAUSE_RET_UNEQUIP_USER,
129 ?SCCP_CAUSE_REF_UNEQUIPPED_USER)
130 end;
131 false ->
132 % If the DPC is not the node itself and the remote DPC, SCCP
133 % and SSN are available, then the MTP-TRANSFER request
134 % primitive is invoked unless the compatibility test returns
135 % the message to SCLC or unless the message is discarded by the
136 % traffic limitation mechanism;
Harald Welte5b0f66f2011-12-04 21:48:12 +0100137 {ok, LsName} = ss7_routes:route_dpc(Pc),
Harald Welteab61a4e2011-10-12 17:19:45 +0200138 {remote, SccpMsg, LsName}
Harald Weltea2ac6832011-10-09 14:32:30 +0200139 end;
140
141% Acccording to 2.3.2 Action (2)
142route_local_out_action(2, SccpMsg, CalledParty) ->
143 % perform GTT
144 case gtt() of
145 undefined ->
146 % if CL -> message return procedure
147 % if CR -> connection refusal
148 msg_return_or_cr_refusal(SccpMsg,
149 ?SCCP_CAUSE_RET_UNEQUIP_USER,
150 ?SCCP_CAUSE_REF_UNEQUIPPED_USER);
151 Dpc ->
152 case pointcode_is_local(Dpc) of
153 true ->
154 % message is passed, based on the message type, to
155 % either SCOC or SCLC;
Harald Welte09145642011-10-10 20:44:10 +0200156 {local, SccpMsg, undefined};
Harald Weltea2ac6832011-10-09 14:32:30 +0200157 false ->
158 % MTP-TRANSFER request primitive is invoked unless the
159 % compatibility test returns the message to SCLC or
160 % unless the message is discarded by the traffic
161 % limitation mechanism
Harald Welte5b0f66f2011-12-04 21:48:12 +0100162 {ok, LsName} = ss7_routes:route_dpc(Dpc),
Harald Welteab61a4e2011-10-12 17:19:45 +0200163 {remote, SccpMsg, LsName}
Harald Weltea2ac6832011-10-09 14:32:30 +0200164 end
165 end;
166
167% Acccording to 2.3.2 Action (3)
168route_local_out_action(3, SccpMsg, CalledParty) ->
169 % The same actions as Action (1) apply, without checking the SSN.
Harald Welte8c9d4e72011-10-10 12:31:09 +0200170 #sccp_addr{global_title = Gt, point_code = Pc} = CalledParty,
171 case pointcode_is_local(Pc) of
172 true ->
173 % pass to either SCOC or SCLC
Harald Welte09145642011-10-10 20:44:10 +0200174 % theoretic case, as we only enter Action(3) for remote DPC
175 {local, SccpMsg, undefined};
Harald Welte8c9d4e72011-10-10 12:31:09 +0200176 false ->
177 % If the DPC is not the node itself and the remote DPC, SCCP
178 % and SSN are available, then the MTP-TRANSFER request
179 % primitive is invoked unless the compatibility test returns
180 % the message to SCLC or unless the message is discarded by the
181 % traffic limitation mechanism;
Harald Welte5b0f66f2011-12-04 21:48:12 +0100182 {ok, LsName} = ss7_routes:route_dpc(Pc),
Harald Welteab61a4e2011-10-12 17:19:45 +0200183 {remote, SccpMsg, LsName}
Harald Welte8c9d4e72011-10-10 12:31:09 +0200184 end;
Harald Weltea2ac6832011-10-09 14:32:30 +0200185
186% Acccording to 2.3.2 Action (4)
187route_local_out_action(4, SccpMsg, CalledParty) ->
188 % insufficient information.
189 msg_return_or_cr_refusal(SccpMsg, ?SCCP_CAUSE_RET_NOTRANS_ADDR,
190 ?SCCP_CAUSE_REF_DEST_UNKNOWN).
191
192
193
194route_cr_connless(Mtp3Msg, SccpMsg) when is_record(SccpMsg, sccp_msg) ->
195 CalledParty = proplists:get_value(called_party_addr, SccpMsg#sccp_msg.parameters),
196 case CalledParty#sccp_addr.route_on_ssn of
197 1 -> % sheet 3 (6)
198 #sccp_addr{ssn = Ssn, point_code = Pc}= CalledParty,
199 % check if the subsystem is available (FIXME: move this into SCLC ?!?)
200 case sccp_user:pid_for_ssn(Ssn, Pc) of
201 {ok, UserPid} ->
202 % forward to SCOC/SCLC
Harald Welte09145642011-10-10 20:44:10 +0200203 {local, SccpMsg, UserPid};
Harald Weltea2ac6832011-10-09 14:32:30 +0200204 {error, Error} ->
205 % invoke connection refusal (if CR) or message return
206 msg_return_or_cr_refusal(SccpMsg,
207 ?SCCP_CAUSE_RET_UNEQUIP_USER,
208 ?SCCP_CAUSE_REF_UNEQUIPPED_USER)
209 end;
210 0 ->
211 % Check for hop counter and increment it
212 MsgPostHop = check_and_dec_hopctr(SccpMsg),
213 MsgClass = proplists:get_value(?SCCP_PNC_PROTOCOL_CLASS,
214 MsgPostHop#sccp_msg.parameters),
215 case MsgClass of
216 0 ->
217 % FIXME: Assign SLS
218 ok;
219 1 ->
220 % FIXME: Map incoming SLS to outgoing SLS
221 ok;
222 _Default ->
223 ok
224 end,
225 % Optional screening function
226 % GTT needs to be performed
227 ok
Harald Welte0a224532012-01-28 14:43:52 +0100228 end.
Harald Weltea2ac6832011-10-09 14:32:30 +0200229 % FIXME: handle UDTS/XUDTS/LUDTS messages (RI=0 check) of C.1/Q.714 (1/12)
230 % FIXME: handle translation already performed == yes) case of C.1/Q.714 (1/12)
Harald Welte0a224532012-01-28 14:43:52 +0100231 %route_main(SccpMsg),
Harald Welteab61a4e2011-10-12 17:19:45 +0200232 %LsName = ss7_routes:route_dpc(),
Harald Welte0a224532012-01-28 14:43:52 +0100233 %LsName = undefined,
234 %{remote, SccpMsg, LsName}.
Harald Weltea2ac6832011-10-09 14:32:30 +0200235
236
237% CR or connectionless message, coming in from MTP
238% return values
Harald Welte09145642011-10-10 20:44:10 +0200239% {local, SccpMsg, UserPid}
Harald Weltea2ac6832011-10-09 14:32:30 +0200240% {remote}
241route_mtp3_sccp_in(Mtp3Msg) when is_record(Mtp3Msg, mtp3_msg) ->
242 {ok, Msg} = sccp_codec:parse_sccp_msg(Mtp3Msg#mtp3_msg.payload),
243 io:format("Parsed Msg: ~p~n", [Msg]),
244 case Msg of
245 #sccp_msg{msg_type = ?SCCP_MSGT_CR} ->
246 route_cr_connless(Mtp3Msg, Msg);
247 _ ->
248 case sccp_codec:is_connectionless(Msg) of
249 true ->
250 route_cr_connless(Mtp3Msg, Msg);
251 false ->
Harald Welte09145642011-10-10 20:44:10 +0200252 {local, Msg, undefined}
Harald Weltea2ac6832011-10-09 14:32:30 +0200253 end
254 end.
255
256% Check if the message has a hop counter; decrement it if yes.
257check_and_dec_hopctr(Msg = #sccp_msg{msg_type = MsgType}) when
258 MsgType == ?SCCP_MSGT_XUDT;
259 MsgType == ?SCCP_MSGT_XUDTS;
260 MsgType == ?SCCP_MSGT_LUDT;
261 MsgType == ?SCCP_MSGT_LUDTS;
262 MsgType == ?SCCP_MSGT_CR ->
263 HopCtr = proplists:get_value(?SCCP_PNC_HOP_COUNTER,
264 Msg#sccp_msg.parameters),
265 if
266 HopCtr =< 1 ->
267 % Error: Hop count expired
268 io:format("SCCP hop count expired~n"),
269 Msg;
270 true ->
271 ParNew = lists:keyreplace(?SCCP_PNC_HOP_COUNTER, 1,
272 Msg#sccp_msg.parameters,
273 { ?SCCP_PNC_HOP_COUNTER, HopCtr -1}),
274 Msg#sccp_msg{parameters = ParNew}
275 end.
276
277route_main(SccpMsg) when is_record(SccpMsg, sccp_msg) ->
278 CalledParty = proplists:get_value(called_party_addr, SccpMsg#sccp_msg.parameters),
279 case CalledParty#sccp_addr.point_code of
280 undefined ->
281 fixme
282 end.
283
284
285% Message return procedure (Section 4.2 / Q.714)
286message_return(SccpMsg = #sccp_msg{msg_type = MsgType}, Cause) when
287 MsgType == ?SCCP_MSGT_XUDT;
288 MsgType == ?SCCP_MSGT_UDT;
289 MsgType == ?SCCP_MSGT_LUDT ->
290 % only return the message if the respective option is set
291 {Class, Opt} = proplists:get_value(protocol_class, SccpMsg#sccp_msg.parameters),
292 if Opt /= 8 ->
293 ok;
294 true ->
295 RetMsg = gen_ret_msg(SccpMsg, Cause),
296 % FIXME: actually return it
297 ok
298 end;
299message_return(_Msg, _Reason) ->
300 ok.
301
302% transform UDT/LUDT/XUDT into UDTS/LUDTS/XUDTS
303gen_ret_msg(SccpMsg = #sccp_msg{msg_type = MsgType, parameters = Params}, Cause) ->
304 % extract information fields required
305 {Class, _Opt} = proplists:get_value(protocol_class, Params),
306 RetMsgType = message_return_type(MsgType),
307 CalledParty = proplists:get_value(called_party_addr, Params),
308 CallingParty = proplists:get_value(calling_party_addr, Params),
309 % build new options proplist
310 Params1 = lists:keyreplace(called_party_addr, 1, Params,
311 {called_party_addr, CallingParty}),
312 Params2 = lists:keyreplace(calling_party_addr, 1, Params1,
313 {calling_party_addr, CalledParty}),
314 Params3 = [{return_cause, Cause}, {protocol_class, {Class, 0}}] ++ Params2,
315 % return the new message
316 SccpMsg#sccp_msg{msg_type = RetMsgType,
317 parameters = Params3}.
318
319connection_refusal(SccpMsg = #sccp_msg{msg_type = ?SCCP_MSGT_CR}, Cause) ->
320 CrefMsg = gen_cref_msg(SccpMsg, Cause),
321 % FIXME: actually return it
322 ok.
323
324gen_cref_msg(SccpMsg = #sccp_msg{msg_type = ?SCCP_MSGT_CR, parameters =
325 Params}, Cause) ->
326 CalledParty = proplists:get_value(called_party_addr, Params),
327 SrcLocalRef = proplists:get_value(src_local_ref, Params),
328 CrefParams = [{dst_local_ref, SrcLocalRef},
329 {refusal_cause, Cause}],
330 % FIXME: what about class / data/ ... ?
331 #sccp_msg{msg_type = ?SCCP_MSGT_CREF, parameters = CrefParams}.
332
333message_return_type(?SCCP_MSGT_XUDT) ->
334 ?SCCP_MSGT_XUDTS;
335message_return_type(?SCCP_MSGT_UDT) ->
336 ?SCCP_MSGT_UDTS;
337message_return_type(?SCCP_MSGT_LUDT) ->
338 ?SCCP_MSGT_LUDTS.
339
340% dummy for now, we don't do GTT yet
341gtt() ->
342 undefined.