blob: 41237c182cfb8cec3aa69a0c9d7db1d7b77869e7 [file] [log] [blame]
Harald Welte9b6a39b2011-10-10 12:38:45 +02001% ITU-T Q.71x SCCP Connection-oriented Control (SCOC)
2
3% (C) 2010 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_scoc).
21-behaviour(gen_fsm).
22
23-include_lib("osmo_ss7/include/osmo_util.hrl").
24-include_lib("osmo_ss7/include/sccp.hrl").
25
26-export([start_link/1]).
27
28-export([init/1, handle_event/3]).
29-export([idle/2, conn_pend_in/2, conn_pend_out/2, active/2, disconnect_pending/2,
30 reset_incoming/2, reset_outgoing/2, bothway_reset/2, wait_conn_conf/2]).
31
32%% gen_fsm callbacks
33
34% Appendix C.4 of Q.714 (all in milliseconds)
35-define(CONNECTION_TIMER, 1 *60*100).
36-define(TX_INACT_TIMER, 5 *60*100).
37-define(RX_INACT_TIMER, 11 *60*100).
38-define(RELEASE_TIMER, 10 *100).
39-define(RELEASE_REP_TIMER, 10 *100).
40-define(INT_TIMER, 1 *60*100).
41-define(GUARD_TIMER, 23 *60*100).
42-define(RESET_TIMER, 10 *100).
43-define(REASSEMBLY_TIMER, 10 *60*100).
44
45-record(state, {
46 role, % client | server
47 user_application, % {MonitorRef, pid()}
48 scrc_pid, % pid()
49 rx_inact_timer, % TRef
50 tx_inact_timer, % TRef
51 local_reference,
52 remote_reference,
53 class,
54 user_pid % pid()
55 }).
56
57% TODO:
58% expedited data
59% class 3
60% segmentation / reassembly
61
62start_link(InitOpts) ->
63 gen_fsm:start_link(sccp_scoc, InitOpts, [{debug, [trace]}]).
64
65init(InitOpts) ->
66 LoopDat = #state{user_pid=proplists:get_value(user_pid, InitOpts),
67 scrc_pid=proplists:get_value(scrc_pid, InitOpts),
68 local_reference=proplists:get_value(local_reference, InitOpts)},
69 io:format("SCOC init Pid=~p LoopDat ~p~n", [self(), LoopDat]),
70 {ok, idle, LoopDat}.
71
72handle_event(stop, _StateName, LoopDat) ->
73 io:format("SCOC received stop event~n"),
74 {stop, normal, LoopDat};
75handle_event({timer_expired, tx_inact_timer}, State, LoopDat) ->
76 % FIXME: T(ias) is expired, send IT message
77 io:format("T(ias) is expired, send IT message~n", []),
78 #state{local_reference = LocRef, remote_reference = RemRef,
79 class = Class} = LoopDat,
80 Params = [{dst_local_ref, RemRef},{src_local_ref, LocRef},
81 {protocol_class, Class}, {seq_segm, 0}, {credit, 0}],
82 Msg = #sccp_msg{msg_type = ?SCCP_MSGT_IT, parameters = Params},
83 gen_fsm:send_event(LoopDat#state.scrc_pid,
84 osmo_util:make_prim('OCRC','CONNECTION-MSG', request, Msg)),
85 {next_state, State, LoopDat};
86handle_event({timer_expired, rx_inact_timer}, State, LoopDat) ->
87 io:format("FIXME: T(iar) is expired, release connection~n", []),
88 % FIXME: Initiate connection release procedure
89 {next_state, State, LoopDat}.
90
91% helper function to send a primitive to the user
92send_user(_LoopDat = #state{user_pid = Pid}, Prim = #primitive{}) ->
93 Pid ! {sccp, Prim}.
94
95% low-level functions regarding activity timers
96restart_tx_inact_timer(LoopDat) ->
97 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
98 [self(), {timer_expired, tx_inact_timer}]),
99 LoopDat#state{tx_inact_timer = Tias}.
100
101restart_rx_inact_timer(LoopDat) ->
102 Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
103 [self(), {timer_expired, rx_inact_timer}]),
104 LoopDat#state{rx_inact_timer = Tiar}.
105
106start_inact_timers(LoopDat) ->
107 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
108 [self(), {timer_expired, tx_inact_timer}]),
109 Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
110 [self(), {timer_expired, rx_inact_timer}]),
111 LoopDat#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}.
112
113stop_inact_timers(#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}) ->
114 timer:cancel(Tiar),
115 timer:cancel(Tias).
116
117
118% -spec idle(#primitive{} | ) -> gen_fsm_state_return().
119
120% STATE Idle
121
122% N-CONNECT.req from user
123idle(#primitive{subsystem = 'N', gen_name = 'CONNECT',
124 spec_name = request, parameters = Param}, LoopDat) ->
125 % local reference already assigned in SCRC when instantiating this SCOC
Harald Welte58020312012-01-24 13:04:50 +0100126 LocalRef = LoopDat#state.local_reference,
Harald Welte9b6a39b2011-10-10 12:38:45 +0200127 % FIXME: determine protocol class and credit
Harald Welte58020312012-01-24 13:04:50 +0100128 ParamDown = Param ++ [{src_local_ref, LocalRef}, {protocol_class, {2,0}}],
Harald Welte9b6a39b2011-10-10 12:38:45 +0200129 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte58020312012-01-24 13:04:50 +0100130 osmo_util:make_prim('OCRC','CONNECTION', indication, ParamDown)),
Harald Welte9b6a39b2011-10-10 12:38:45 +0200131 % start connection timer
132 {next_state, conn_pend_out, LoopDat, ?CONNECTION_TIMER};
133
134% RCOC-CONNECTION.req from SCRC
135idle(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION',
136 spec_name = indication, parameters = Params}, LoopDat) ->
137 % associate remote reference to connection section
138 RemRef = proplists:get_value(src_local_ref, Params),
139 % determine protocol class and FIXME: credit
140 Class = proplists:get_value(protocol_class, Params),
141 LoopDat1 = LoopDat#state{remote_reference = RemRef, class = Class},
142 % send N-CONNECT.ind to user
143 send_user(LoopDat1, osmo_util:make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
144 %#primitive{subsystem = 'N', gen_name = 'CONNECT', spec_name = indication}
145 {next_state, conn_pend_in, LoopDat1};
146
147% RCOC-ROUTING_FAILURE.ind from SCRC
148idle(#primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
149 spec_name = indication}, LoopDat) ->
150 gen_fsm:send_event(LoopDat#state.scrc_pid,
151 osmo_util:make_prim('OCRC', 'CONNECTION REFUSED', indication)),
152 {next_state, idle, LoopDat};
153
154%FIXME: request type 2 ?!?
155
156% RCOC-RELEASED.ind from SCRC
157idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASED',
158 spec_name = indication}, LoopDat) ->
159 gen_fsm:send_event(LoopDat#state.scrc_pid,
160 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
161 {next_state, idle, LoopDat};
162
163% RCOC-RELEASE_COMPLETE.ind from SCRC
164idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASE COMPLETE',
165 spec_name = indication}, LoopDat) ->
166 {next_state, idle, LoopDat};
167
168idle(#primitive{subsystem= 'RCOC', gen_name = 'DATA',
169 spec_name = indication, parameters = Param}, LoopDat) ->
170 % FIXME: if source reference, send error
171 send_user(LoopDat, osmo_util:make_prim('N', 'DATA', indication, Param)),
172 {next_state, idle, LoopDat}.
173
174% STATE Connection pending incoming
175conn_pend_in(#primitive{subsystem = 'N', gen_name = 'CONNECT',
176 spec_name = response, parameters = Param}, LoopDat) ->
177 io:format("SCOC N-CONNECT.resp LoopDat ~p~n", [LoopDat]),
178 % assign local reference, SLS, protocol class and credit for inc section
179 OutParam = [{dst_local_ref, LoopDat#state.remote_reference},
180 {src_local_ref, LoopDat#state.local_reference},
181 {protocol_class, LoopDat#state.class}] ++ Param,
182 gen_fsm:send_event(LoopDat#state.scrc_pid,
183 osmo_util:make_prim('OCRC', 'CONNECTION', confirm, OutParam)),
184 % start inactivity timers
185 LoopDat1 = start_inact_timers(LoopDat),
186 {next_state, active, LoopDat1};
187conn_pend_in(any_npdu_type, LoopDat) ->
188 {next_state, conn_pend_in, LoopDat};
189conn_pend_in(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
190 spec_name = request, parameters = Param}, LoopDat) ->
191 % release resourcers (local ref may have to be released an frozen)
192 gen_fsm:send_event(LoopDat#state.scrc_pid,
193 osmo_util:make_prim('OCRC', 'CONNECTION REFUSED', indication, Param)),
194 {next_state, idle, LoopDat}.
195
196
197disc_ind_stop_rel_3(LoopDat) ->
198 % send N-DISCONNECT.ind to user
199 send_user(LoopDat, osmo_util:make_prim('N', 'DISCONNECT',indication)),
200 % stop inactivity timers
201 stop_inact_timers(LoopDat),
202 gen_fsm:send_event(LoopDat#state.scrc_pid,
203 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
204 % start release timer
205 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
206
207rel_res_disc_ind_idle_2(LoopDat) ->
208 % release resources and local reference (freeze)
209 % send N-DISCONNECT.ind to user
210 send_user(LoopDat, osmo_util:make_prim('N', 'DISCONNECT', indication)),
211 {next_state, idle, LoopDat}.
212
213
214% STATE Connection pending outgoing
215conn_pend_out(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
216 spec_name = request}, LoopDat) ->
217 % FIXME: what about the connection timer ?
218 {next_state, wait_conn_conf, LoopDat};
219conn_pend_out(timeout, LoopDat) ->
220 rel_res_disc_ind_idle_2(LoopDat);
221conn_pend_out(routing_failure, LoopDat) ->
222 rel_res_disc_ind_idle_2(LoopDat);
223conn_pend_out(released, LoopDat) ->
224 gen_fsm:send_event(LoopDat#state.scrc_pid,
225 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
226 rel_res_disc_ind_idle_2(LoopDat);
227% other N-PDU Type
228conn_pend_out(other_npdu_type, LoopDat) ->
229 rel_res_disc_ind_idle_2(LoopDat);
230conn_pend_out(connection_refused, LoopDat) ->
231 rel_res_disc_ind_idle_2(LoopDat);
232conn_pend_out(connection_confirm, LoopDat) ->
233 % start inactivity timers
234 LoopDat1 = start_inact_timers(LoopDat),
235 % assign protocol class and associate remote reference to connection
236 % send N-CONNECT.conf to user
237 send_user(LoopDat1, #primitive{subsystem = 'N', gen_name = 'CONNECT',
238 spec_name = confirm}),
239 {next_state, active, LoopDat1}.
240
241stop_c_tmr_rel_idle_5(LoopDat) ->
242 % stop connection timer (implicit)
243 % release resources and local reference
244 {next_state, idle, LoopDat}.
245
246rel_freeze_idle(LoopDat) ->
247 {next_state, idle, LoopDat}.
248
249% STATE Wait connection confirmed
250wait_conn_conf(released, LoopDat) ->
251 gen_fsm:send_event(LoopDat#state.scrc_pid,
252 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
253 stop_c_tmr_rel_idle_5(LoopDat);
254wait_conn_conf(connection_confirm, LoopDat) ->
255 % stop connection timer (implicit)
256 % associate remote reference to connection
257 relsd_tmr_disc_pend_6(LoopDat);
258wait_conn_conf(other_npdu_type, LoopDat) ->
259 % stop connection timer (implicit)
260 rel_freeze_idle(LoopDat);
261wait_conn_conf(timeout, LoopDat) ->
262 stop_c_tmr_rel_idle_5(LoopDat);
263wait_conn_conf(connection_refused, LoopDat) ->
264 stop_c_tmr_rel_idle_5(LoopDat);
265wait_conn_conf(routing_failure, LoopDat) ->
266 stop_c_tmr_rel_idle_5(LoopDat).
267
268
269relsd_tmr_disc_pend_6(LoopDat) ->
270 gen_fsm:send_event(LoopDat#state.scrc_pid,
271 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
272 % start release timer
273 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
274
275% STATE Active
276active(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
277 spec_name = request}, LoopDat) ->
278 % stop inactivity timers
279 start_inact_timers(LoopDat),
280 relsd_tmr_disc_pend_6(LoopDat);
281active(internal_disconnect, LoopDat) ->
282 disc_ind_stop_rel_3(LoopDat);
283active(connection_refused, LoopDat) ->
284 {next_state, active, LoopDat};
285active(connection_confirm, LoopDat) ->
286 {next_state, active, LoopDat};
287active(release_complete, LoopDat) ->
288 {next_state, active, LoopDat};
289active(released, LoopDat) ->
290 % send N-DISCONNECT.ind to user
291 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
292 spec_name = indication}),
293 % release resources and local reference (freeze)
294 % stop inactivity timers
295 stop_inact_timers(LoopDat),
296 gen_fsm:send_event(LoopDat#state.scrc_pid,
297 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
298 {next_state, idle, LoopDat};
299active(error, LoopDat) ->
300 % send N-DISCONNECT.ind to user
301 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
302 spec_name = indication}),
303 % release resources and local reference (freeze)
304 % stop inactivity timers
305 stop_inact_timers(LoopDat),
306 gen_fsm:send_event(LoopDat#state.scrc_pid,
307 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
308 {next_state, idle, LoopDat};
309active(rcv_inact_tmr_exp, LoopDat) ->
310 disc_ind_stop_rel_3(LoopDat);
311active(routing_failure, LoopDat) ->
312 % send N-DISCONNECT.ind to user
313 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
314 spec_name = indication}),
315 % stop inactivity timers
316 stop_inact_timers(LoopDat),
317 % start release timer
318 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER};
319% Connection release procedures at destination node
320%active(internal_disconnect) ->
321% Data transfer procedures
322active(#primitive{subsystem = 'N', gen_name = 'DATA',
323 spec_name = request, parameters = Param}, LoopDat) ->
324 % FIXME Segment NSDU and assign value to bit M
325 % FIXME handle protocol class 3
326 gen_fsm:send_event(LoopDat#state.scrc_pid, {dt1, []}),
327 % restart send inactivity timer
328 LoopDat1 = restart_tx_inact_timer(LoopDat),
329 {next_state, active, LoopDat1};
330active(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION-MSG',
331 spec_name = indication, parameters = Msg}, LoopDat) ->
332 % restart receive inactivity timer
333 LoopDat1 = restart_rx_inact_timer(LoopDat),
334 % FIXME handle protocol class 3
335 % FIXME check for M-bit=1 and put data in Rx queue
336 % N-DATA.ind to user
337 UserData = proplists:get_value(user_data, Msg#sccp_msg.parameters),
338 send_user(LoopDat, osmo_util:make_prim('N', 'DATA', indication, {user_data, UserData})),
339 {next_state, active, LoopDat1};
340% Reset procedures
341active(#primitive{subsystem = 'N', gen_name = 'RESET',
342 spec_name = request, parameters = Param}, LoopDat) ->
343 gen_fsm:send_event(LoopDat#state.scrc_pid,
344 osmo_util:make_prim('OCRC', 'RESET', request, Param)),
345 % start reset timer
346 % restart send inact timer
347 LoopDat1 = restart_tx_inact_timer(LoopDat),
348 % reset variables and discard all queued and unacked msgs
349 {next_state, reset_outgoing, LoopDat1, ?RESET_TIMER};
350active(internal_reset_req, LoopDat) ->
351 % N-RESET.ind to user
352 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
353 spec_name = indication}),
354 gen_fsm:send_event(LoopDat#state.scrc_pid,
355 osmo_util:make_prim('OCRC', 'RESET', request)),
356 % start reset timer
357 % restart send inact timer
358 LoopDat1 = restart_tx_inact_timer(LoopDat),
359 % reset variables and discard all queued and unacked msgs
360 {next_state, bothway_reset, LoopDat1, ?RESET_TIMER};
361active(reset_confirm, LoopDat) ->
362 % discard received message
363 {next_state, active, LoopDat};
364active(reset_req, LoopDat) ->
365 % restart send inactivity timer
366 LoopDat1 = restart_tx_inact_timer(LoopDat),
367 % N-RESET.ind to user
368 send_user(LoopDat, osmo_util:make_prim('N', 'RESET', indication)),
369 % reset variables and discard all queued and unacked msgs
370 {next_state, reset_incoming, LoopDat1}.
371
372rel_res_stop_tmr_12(LoopDat) ->
373 % release resources and local reference (freeze)
374 % stop release and interval timers
375 {next_state, idle, LoopDat}.
376
377% STATE Disconnect pending
378disconnect_pending(release_complete, LoopDat) ->
379 rel_res_stop_tmr_12(LoopDat);
380disconnect_pending(released_error, LoopDat) ->
381 rel_res_stop_tmr_12(LoopDat);
382disconnect_pending(routing_failure, LoopDat) ->
383 {next_state, disconnect_pending, LoopDat};
384disconnect_pending(other_npdu_type, LoopDat) ->
385 % discared received message
386 {next_state, disconnect_pending, LoopDat};
387disconnect_pending(timeout, LoopDat) ->
388 gen_fsm:send_event(LoopDat#state.scrc_pid,
389 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
390 % start interval timer
391 % FIXME start repeat release timer
392 {next_state, disconnect_pending, ?RELEASE_REP_TIMER};
393disconnect_pending(intv_tmr_exp, LoopDat) ->
394 % inform maintenance
395 rel_res_stop_tmr_12(LoopDat);
396% FIXME: this is currently ending up in normal 'timeout' above
397disconnect_pending(repeat_release_tmr_exp, LoopDat) ->
398 gen_fsm:send_event(LoopDat#state.scrc_pid,
399 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
400 % FIXME restart repeat release timer
401 {next_state, disconnect_pending}.
402
403res_out_res_conf_req(LoopDat) ->
404 % N-RESET.conf to user
405 send_user(LoopDat, osmo_util:make_prim('N', 'RESET', confirm)),
406 % stop reset timer (implicit)
407 % restart receive inactivity timer
408 LoopDat1 = restart_rx_inact_timer(LoopDat),
409 % resume data transfer
410 {next_state, active, LoopDat1}.
411
412% STATE Reset outgoing
413reset_outgoing(#primitive{subsystem = 'N', gen_name = 'DATA',
414 spec_name = request, parameters = Params}, LoopDat) ->
415 % FIXME received information ?!?
416 {next_state, reset_outgoing, LoopDat};
417reset_outgoing(#primitive{subsystem = 'N', gen_name = 'EXPEDITED DATA',
418 spec_name = request, parameters = Params}, LoopDat) ->
419 % FIXME received information ?!?
420 {next_state, reset_outgoing, LoopDat};
421reset_outgoing(timeout, LoopDat) ->
422 % FIXME check for temporary connection section
423 % inform maintenance
424 {next_state, maintenance_Blocking, LoopDat};
425%reset_outgoing(error, LoopDat) ->
426%reset_outgoing(released, LoopDat) ->
427reset_outgoing(other_npdu_type, LoopDat) ->
428 % discard received message
429 {next_state, reset_outgoing, LoopDat};
430reset_outgoing(reset_confirm, LoopDat) ->
431 res_out_res_conf_req(LoopDat);
432reset_outgoing(reset_request, LoopDat) ->
433 res_out_res_conf_req(LoopDat).
434
435bway_res_req_resp(LoopDat) ->
436 {next_state, reset_outgoing, LoopDat}.
437
438bway_res_res_conf_req(LoopDat) ->
439 % N-RESET.conf to user
440 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
441 spec_name = confirm}),
442 % stop reset timer (implicit)
443 % restart receive inactivity timer
444 LoopDat1 = restart_rx_inact_timer(LoopDat),
445 {next_state, reset_incoming, LoopDat1}.
446
447% STATE Bothway Reset
448bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
449 spec_name = request, parameters = Params}, LoopDat) ->
450 bway_res_req_resp(LoopDat);
451bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
452 spec_name = response, parameters = Params}, LoopDat) ->
453 bway_res_req_resp(LoopDat);
454bothway_reset(timeout, LoopDat) ->
455 % FIXME check for temporary connection section
456 % inform maintenance
457 {next_state, maintenance_Blocking, LoopDat};
458%bothway_reset(error, LoopDat) ->
459%bothway_reset(released, LoopDat) ->
460bothway_reset(other_npdu_type, LoopDat) ->
461 % discard received message
462 {next_state, bothway_reset, LoopDat}.
463
464% STATE Reset incoming
465reset_incoming(#primitive{subsystem = 'N', gen_name = 'RESET',
466 spec_name = request, parameters = Params}, LoopDat) ->
467 % received information
468 {nest_state, reset_incoming, LoopDat};
469%reset_incoming(error, LoopDat) ->
470%reset_incoming(released, LoopDat) ->
471reset_incoming(other_npdu_type, LoopDat) ->
472 % discard received message
473 % internal reset request
474 {next_state, active, LoopDat}.
475% FIXME: response or request
476%reset_incoming(