blob: 9e461d9e9d733533b9ce520ddf2f3b2c90a10c1f [file] [log] [blame]
Harald Welte033cef02010-12-19 22:47:14 +01001% 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("sccp.hrl").
24
25-export([start_link/1]).
26
27-export([init/1, handle_event/3]).
28-export([idle/2, conn_pend_in/2, conn_pend_out/2, active/2, disconnect_pending/2,
29 reset_incoming/2, reset_outgoing/2, bothway_reset/2, wait_conn_conf/2]).
30
31-export([make_prim/4, make_prim/3]).
32
33%% gen_fsm callbacks
34
35% Appendix C.4 of Q.714 (all in milliseconds)
36-define(CONNECTION_TIMER, 1 *60*100).
37-define(TX_INACT_TIMER, 5 *60*100).
38-define(RX_INACT_TIMER, 11 *60*100).
39-define(RELEASE_TIMER, 10 *100).
40-define(RELEASE_REP_TIMER, 10 *100).
41-define(INT_TIMER, 1 *60*100).
42-define(GUARD_TIMER, 23 *60*100).
43-define(RESET_TIMER, 10 *100).
44-define(REASSEMBLY_TIMER, 10 *60*100).
45
46-record(state, {
47 role, % client | server
48 user_application, % {MonitorRef, pid()}
49 scrc_pid, % pid()
50 rx_inact_timer, % TRef
51 tx_inact_timer, % TRef
52 local_reference,
53 remote_reference,
54 class,
55 user_pid % pid()
56 }).
57
58% TODO:
59% expedited data
60% class 3
61% segmentation / reassembly
62
63start_link(InitOpts) ->
64 gen_fsm:start_link(sccp_scoc, InitOpts, [{debug, [trace]}]).
65
66init(InitOpts) ->
67 LoopDat = #state{user_pid=proplists:get_value(user_pid, InitOpts),
68 scrc_pid=proplists:get_value(scrc_pid, InitOpts),
69 local_reference=proplists:get_value(local_reference, InitOpts)},
70 io:format("SCOC init Pid=~p LoopDat ~p~n", [self(), LoopDat]),
71 {ok, idle, LoopDat}.
72
73handle_event(stop, _StateName, LoopDat) ->
74 io:format("SCOC received stop event~n"),
75 {stop, normal, LoopDat};
76handle_event({timer_expired, tx_inact_timer}, State, LoopDat) ->
77 % FIXME: T(ias) is expired, send IT message
78 io:format("FIXME: T(ias) is expired, send IT message~n", []),
79 {next_state, State, LoopDat};
80handle_event({timer_expired, rx_inact_timer}, State, LoopDat) ->
81 io:format("FIXME: T(iar) is expired, release connection~n", []),
82 % FIXME: Initiate connection release procedure
83 {next_state, State, LoopDat}.
84
85% helper function to create a #primitive record
86make_prim(Subsys, GenName, SpecName) ->
87 make_prim(Subsys, GenName, SpecName, []).
88make_prim(Subsys, GenName, SpecName, Param) ->
89 #primitive{subsystem = Subsys, gen_name = GenName,
90 spec_name = SpecName, parameters = Param}.
91
92% helper function to send a primitive to the user
93send_user(LoopDat = #state{user_pid = Pid}, Prim = #primitive{}) ->
94 Pid ! {sccp, Prim}.
95
96% low-level functions regarding activity timers
97restart_tx_inact_timer(LoopDat) ->
98 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
99 [self(), {timer_expired, tx_inact_timer}]),
100 LoopDat#state{tx_inact_timer = Tias}.
101
102restart_rx_inact_timer(LoopDat) ->
103 Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
104 [self(), {timer_expired, rx_inact_timer}]),
105 LoopDat#state{rx_inact_timer = Tiar}.
106
107start_inact_timers(LoopDat) ->
108 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
109 [self(), {timer_expired, tx_inact_timer}]),
110 Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
111 [self(), {timer_expired, rx_inact_timer}]),
112 LoopDat#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}.
113
114stop_inact_timers(LoopDat = #state{rx_inact_timer = Tiar, tx_inact_timer = Tias}) ->
115 timer:cancel(Tiar),
116 timer:cancel(Tias).
117
118
119% -spec idle(#primitive{} | ) -> gen_fsm_state_return().
120
121% STATE Idle
122
123% N-CONNECT.req from user
124idle(Prim = #primitive{subsystem = 'N', gen_name = 'CONNECT',
125 spec_name = request, parameters = Param}, LoopDat) ->
126 % assign local reference and SLS
127 % determine protocol class and credit
128 LoopDat1 = LoopDat#state{local_reference = make_ref(), class = 2},
129 gen_fsm:send_event(LoopDat1#state.scrc_pid,
130 make_prim('OCRC','CONNECTION', indication, Param)),
131 % start connection timer
132 {next_state, conn_pend_out, LoopDat1, ?CONNECTION_TIMER};
133
134% RCOC-CONNECTION.req from SCRC
135idle(Prim = #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, 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(Prim = #primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
149 spec_name = indication, parameters = Param}, LoopDat) ->
150 gen_fsm:send_event(LoopDat#state.scrc_pid,
151 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(Prim = #primitive{subsystem = 'RCOC', gen_name = 'RELEASED',
158 spec_name = indication}, LoopDat) ->
159 gen_fsm:send_event(LoopDat#state.scrc_pid,
160 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
161 {next_state, idle, LoopDat};
162
163% RCOC-RELEASE_COMPLETE.ind from SCRC
164idle(Prim = #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, make_prim('N', 'DATA', indication, Param)),
172 {next_state, idle, LoopDat}.
173
174% STATE Connection pending incoming
175conn_pend_in(Prim = #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 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(Prim = #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 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, make_prim('N', 'DISCONNECT',indication)),
200 % stop inactivity timers
201 stop_inact_timers(LoopDat),
202 gen_fsm:send_event(LoopDat#state.scrc_pid,
203 make_prim('OCRC', 'RELESED', 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, make_prim('N', 'DISCONNECT', indication)),
211 {next_state, idle, LoopDat}.
212
213
214% STATE Connection pending outgoing
215conn_pend_out(Prim = #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
216 spec_name = request, parameters = Param}, 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 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 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 make_prim('OCRC', 'RELEASED', indication)),
272 % start release timer
273 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
274
275% STATE Active
276active(Prim = #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
277 spec_name = request, parameters = Param}, 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 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 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(Prim = #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({dt1, Param}, LoopDat) ->
331 % restart receive inactivity timer
332 LoopDat1 = restart_rx_inact_timer(LoopDat),
333 % FIXME handle protocol class 3
334 % FIXME check for M-bit=1 and put data in Rx queue
335 % N-DATA.ind to user
336 send_user(LoopDat, make_prim('N', 'DATA', indication, Param)),
337 {next_state, active, LoopDat1};
338% Reset procedures
339active(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
340 spec_name = request, parameters = Param}, LoopDat) ->
341 gen_fsm:send_event(LoopDat#state.scrc_pid,
342 make_prim('OCRC', 'RESET', request, Param)),
343 % start reset timer
344 % restart send inact timer
345 LoopDat1 = restart_tx_inact_timer(LoopDat),
346 % reset variables and discard all queued and unacked msgs
347 {next_state, reset_outgoing, LoopDat1, ?RESET_TIMER};
348active(internal_reset_req, LoopDat) ->
349 % N-RESET.ind to user
350 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
351 spec_name = indication}),
352 gen_fsm:send_event(LoopDat#state.scrc_pid,
353 make_prim('OCRC', 'RESET', request)),
354 % start reset timer
355 % restart send inact timer
356 LoopDat1 = restart_tx_inact_timer(LoopDat),
357 % reset variables and discard all queued and unacked msgs
358 {next_state, bothway_reset, LoopDat1, ?RESET_TIMER};
359active(reset_confirm, LoopDat) ->
360 % discard received message
361 {next_state, active, LoopDat};
362active(reset_req, LoopDat) ->
363 % restart send inactivity timer
364 LoopDat1 = restart_tx_inact_timer(LoopDat),
365 % N-RESET.ind to user
366 send_user(LoopDat, make_prim('N', 'RESET', indication)),
367 % reset variables and discard all queued and unacked msgs
368 {next_state, reset_incoming, LoopDat1}.
369
370rel_res_stop_tmr_12(LoopDat) ->
371 % release resources and local reference (freeze)
372 % stop release and interval timers
373 {next_state, idle, LoopDat}.
374
375% STATE Disconnect pending
376disconnect_pending(release_complete, LoopDat) ->
377 rel_res_stop_tmr_12(LoopDat);
378disconnect_pending(released_error, LoopDat) ->
379 rel_res_stop_tmr_12(LoopDat);
380disconnect_pending(routing_failure, LoopDat) ->
381 {next_state, disconnect_pending};
382disconnect_pending(other_npdu_type, LoopDat) ->
383 % discared received message
384 {next_state, disconnect_pending};
385disconnect_pending(timeout, LoopDat) ->
386 gen_fsm:send_event(LoopDat#state.scrc_pid,
387 make_prim('OCRC', 'RELEASED', indication)),
388 % start interval timer
389 % FIXME start repeat release timer
390 {next_state, disconnect_pending, ?RELEASE_REP_TIMER};
391disconnect_pending(intv_tmr_exp, LoopDat) ->
392 % inform maintenance
393 rel_res_stop_tmr_12(LoopDat);
394% FIXME: this is currently ending up in normal 'timeout' above
395disconnect_pending(repeat_release_tmr_exp, LoopDat) ->
396 gen_fsm:send_event(LoopDat#state.scrc_pid,
397 make_prim('OCRC', 'RELEASED', indication)),
398 % FIXME restart repeat release timer
399 {next_state, disconnect_pending}.
400
401res_out_res_conf_req(LoopDat) ->
402 % N-RESET.conf to user
403 send_user(LoopDat, make_prim('N', 'RESET', confirm)),
404 % stop reset timer (implicit)
405 % restart receive inactivity timer
406 LoopDat1 = restart_rx_inact_timer(LoopDat),
407 % resume data transfer
408 {next_state, active, LoopDat1}.
409
410% STATE Reset outgoing
411reset_outgoing(Prim = #primitive{subsystem = 'N', gen_name = 'DATA',
412 spec_name = request, parameters = Params}, LoopDat) ->
413 % FIXME received information ?!?
414 {next_state, reset_outgoing, LoopDat};
415reset_outgoing(Prim = #primitive{subsystem = 'N', gen_name = 'EXPEDITED DATA',
416 spec_name = request, parameters = Params}, LoopDat) ->
417 % FIXME received information ?!?
418 {next_state, reset_outgoing, LoopDat};
419reset_outgoing(timeout, LoopDat) ->
420 % FIXME check for temporary connection section
421 % inform maintenance
422 {next_state, maintenance_Blocking, LoopDat};
423%reset_outgoing(error, LoopDat) ->
424%reset_outgoing(released, LoopDat) ->
425reset_outgoing(other_npdu_type, LoopDat) ->
426 % discard received message
427 {next_state, reset_outgoing, LoopDat};
428reset_outgoing(reset_confirm, LoopDat) ->
429 res_out_res_conf_req(LoopDat);
430reset_outgoing(reset_request, LoopDat) ->
431 res_out_res_conf_req(LoopDat).
432
433bway_res_req_resp(LoopDat) ->
434 {next_state, reset_outgoing, LoopDat}.
435
436bway_res_res_conf_req(LoopDat) ->
437 % N-RESET.conf to user
438 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
439 spec_name = confirm}),
440 % stop reset timer (implicit)
441 % restart receive inactivity timer
442 LoopDat1 = restart_rx_inact_timer(LoopDat),
443 {next_state, reset_incoming, LoopDat1}.
444
445% STATE Bothway Reset
446bothway_reset(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
447 spec_name = request, parameters = Params}, LoopDat) ->
448 bway_res_req_resp(LoopDat);
449bothway_reset(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
450 spec_name = response, parameters = Params}, LoopDat) ->
451 bway_res_req_resp(LoopDat);
452bothway_reset(timeout, LoopDat) ->
453 % FIXME check for temporary connection section
454 % inform maintenance
455 {next_state, maintenance_Blocking, LoopDat};
456%bothway_reset(error, LoopDat) ->
457%bothway_reset(released, LoopDat) ->
458bothway_reset(other_npdu_type, LoopDat) ->
459 % discard received message
460 {next_state, bothway_reset, LoopDat}.
461
462% STATE Reset incoming
463reset_incoming(Prim = #primitive{subsystem = 'N', gen_name = 'RESET',
464 spec_name = request, parameters = Params}, LoopDat) ->
465 % received information
466 {nest_state, reset_incoming, LoopDat};
467%reset_incoming(error, LoopDat) ->
468%reset_incoming(released, LoopDat) ->
469reset_incoming(other_npdu_type, LoopDat) ->
470 % discard received message
471 % internal reset request
472 {next_state, active, LoopDat}.
473% FIXME: response or request
474%reset_incoming(