blob: f726eb23683c80fcd0b2990540f7c69c668cc465 [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
Harald Welte0f2f5962011-04-04 15:59:49 +020023-include("osmo_util.hrl").
Harald Welte033cef02010-12-19 22:47:14 +010024-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
Harald Welte033cef02010-12-19 22:47:14 +010032%% 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
Harald Weltefba08e42010-12-20 12:40:00 +010077 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,
Harald Welte0f2f5962011-04-04 15:59:49 +020084 osmo_util:make_prim('OCRC','CONNECTION-MSG', request, Msg)),
Harald Welte033cef02010-12-19 22:47:14 +010085 {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
Harald Welte033cef02010-12-19 22:47:14 +010091% helper function to send a primitive to the user
Harald Welteda95baa2010-12-20 12:38:34 +010092send_user(_LoopDat = #state{user_pid = Pid}, Prim = #primitive{}) ->
Harald Welte033cef02010-12-19 22:47:14 +010093 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
Harald Welteda95baa2010-12-20 12:38:34 +0100113stop_inact_timers(#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}) ->
Harald Welte033cef02010-12-19 22:47:14 +0100114 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
Harald Welteda95baa2010-12-20 12:38:34 +0100123idle(#primitive{subsystem = 'N', gen_name = 'CONNECT',
124 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100125 % assign local reference and SLS
126 % determine protocol class and credit
127 LoopDat1 = LoopDat#state{local_reference = make_ref(), class = 2},
128 gen_fsm:send_event(LoopDat1#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200129 osmo_util:make_prim('OCRC','CONNECTION', indication, Param)),
Harald Welte033cef02010-12-19 22:47:14 +0100130 % start connection timer
131 {next_state, conn_pend_out, LoopDat1, ?CONNECTION_TIMER};
132
133% RCOC-CONNECTION.req from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100134idle(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION',
135 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100136 % associate remote reference to connection section
137 RemRef = proplists:get_value(src_local_ref, Params),
138 % determine protocol class and FIXME: credit
139 Class = proplists:get_value(protocol_class, Params),
140 LoopDat1 = LoopDat#state{remote_reference = RemRef, class = Class},
141 % send N-CONNECT.ind to user
Harald Welte0f2f5962011-04-04 15:59:49 +0200142 send_user(LoopDat1, osmo_util:make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
Harald Welte033cef02010-12-19 22:47:14 +0100143 %#primitive{subsystem = 'N', gen_name = 'CONNECT', spec_name = indication}
144 {next_state, conn_pend_in, LoopDat1};
145
146% RCOC-ROUTING_FAILURE.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100147idle(#primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
148 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100149 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200150 osmo_util:make_prim('OCRC', 'CONNECTION REFUSED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100151 {next_state, idle, LoopDat};
152
153%FIXME: request type 2 ?!?
154
155% RCOC-RELEASED.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100156idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASED',
157 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100158 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200159 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100160 {next_state, idle, LoopDat};
161
162% RCOC-RELEASE_COMPLETE.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100163idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASE COMPLETE',
164 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100165 {next_state, idle, LoopDat};
166
167idle(#primitive{subsystem= 'RCOC', gen_name = 'DATA',
168 spec_name = indication, parameters = Param}, LoopDat) ->
169 % FIXME: if source reference, send error
Harald Welte0f2f5962011-04-04 15:59:49 +0200170 send_user(LoopDat, osmo_util:make_prim('N', 'DATA', indication, Param)),
Harald Welte033cef02010-12-19 22:47:14 +0100171 {next_state, idle, LoopDat}.
172
173% STATE Connection pending incoming
Harald Welteda95baa2010-12-20 12:38:34 +0100174conn_pend_in(#primitive{subsystem = 'N', gen_name = 'CONNECT',
175 spec_name = response, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100176 io:format("SCOC N-CONNECT.resp LoopDat ~p~n", [LoopDat]),
177 % assign local reference, SLS, protocol class and credit for inc section
178 OutParam = [{dst_local_ref, LoopDat#state.remote_reference},
179 {src_local_ref, LoopDat#state.local_reference},
180 {protocol_class, LoopDat#state.class}] ++ Param,
181 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200182 osmo_util:make_prim('OCRC', 'CONNECTION', confirm, OutParam)),
Harald Welte033cef02010-12-19 22:47:14 +0100183 % start inactivity timers
184 LoopDat1 = start_inact_timers(LoopDat),
185 {next_state, active, LoopDat1};
186conn_pend_in(any_npdu_type, LoopDat) ->
187 {next_state, conn_pend_in, LoopDat};
Harald Welteda95baa2010-12-20 12:38:34 +0100188conn_pend_in(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
189 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100190 % release resourcers (local ref may have to be released an frozen)
191 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200192 osmo_util:make_prim('OCRC', 'CONNECTION REFUSED', indication, Param)),
Harald Welte033cef02010-12-19 22:47:14 +0100193 {next_state, idle, LoopDat}.
194
195
196disc_ind_stop_rel_3(LoopDat) ->
197 % send N-DISCONNECT.ind to user
Harald Welte0f2f5962011-04-04 15:59:49 +0200198 send_user(LoopDat, osmo_util:make_prim('N', 'DISCONNECT',indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100199 % stop inactivity timers
200 stop_inact_timers(LoopDat),
201 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200202 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100203 % start release timer
204 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
205
206rel_res_disc_ind_idle_2(LoopDat) ->
207 % release resources and local reference (freeze)
208 % send N-DISCONNECT.ind to user
Harald Welte0f2f5962011-04-04 15:59:49 +0200209 send_user(LoopDat, osmo_util:make_prim('N', 'DISCONNECT', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100210 {next_state, idle, LoopDat}.
211
212
213% STATE Connection pending outgoing
Harald Welteda95baa2010-12-20 12:38:34 +0100214conn_pend_out(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
215 spec_name = request}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100216 % FIXME: what about the connection timer ?
217 {next_state, wait_conn_conf, LoopDat};
218conn_pend_out(timeout, LoopDat) ->
219 rel_res_disc_ind_idle_2(LoopDat);
220conn_pend_out(routing_failure, LoopDat) ->
221 rel_res_disc_ind_idle_2(LoopDat);
222conn_pend_out(released, LoopDat) ->
223 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200224 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100225 rel_res_disc_ind_idle_2(LoopDat);
226% other N-PDU Type
227conn_pend_out(other_npdu_type, LoopDat) ->
228 rel_res_disc_ind_idle_2(LoopDat);
229conn_pend_out(connection_refused, LoopDat) ->
230 rel_res_disc_ind_idle_2(LoopDat);
231conn_pend_out(connection_confirm, LoopDat) ->
232 % start inactivity timers
233 LoopDat1 = start_inact_timers(LoopDat),
234 % assign protocol class and associate remote reference to connection
235 % send N-CONNECT.conf to user
236 send_user(LoopDat1, #primitive{subsystem = 'N', gen_name = 'CONNECT',
237 spec_name = confirm}),
238 {next_state, active, LoopDat1}.
239
240stop_c_tmr_rel_idle_5(LoopDat) ->
241 % stop connection timer (implicit)
242 % release resources and local reference
243 {next_state, idle, LoopDat}.
244
245rel_freeze_idle(LoopDat) ->
246 {next_state, idle, LoopDat}.
247
248% STATE Wait connection confirmed
249wait_conn_conf(released, LoopDat) ->
250 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200251 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100252 stop_c_tmr_rel_idle_5(LoopDat);
253wait_conn_conf(connection_confirm, LoopDat) ->
254 % stop connection timer (implicit)
255 % associate remote reference to connection
256 relsd_tmr_disc_pend_6(LoopDat);
257wait_conn_conf(other_npdu_type, LoopDat) ->
258 % stop connection timer (implicit)
259 rel_freeze_idle(LoopDat);
260wait_conn_conf(timeout, LoopDat) ->
261 stop_c_tmr_rel_idle_5(LoopDat);
262wait_conn_conf(connection_refused, LoopDat) ->
263 stop_c_tmr_rel_idle_5(LoopDat);
264wait_conn_conf(routing_failure, LoopDat) ->
265 stop_c_tmr_rel_idle_5(LoopDat).
266
267
268relsd_tmr_disc_pend_6(LoopDat) ->
269 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200270 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100271 % start release timer
272 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
273
274% STATE Active
Harald Welteda95baa2010-12-20 12:38:34 +0100275active(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
276 spec_name = request}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100277 % stop inactivity timers
278 start_inact_timers(LoopDat),
279 relsd_tmr_disc_pend_6(LoopDat);
280active(internal_disconnect, LoopDat) ->
281 disc_ind_stop_rel_3(LoopDat);
282active(connection_refused, LoopDat) ->
283 {next_state, active, LoopDat};
284active(connection_confirm, LoopDat) ->
285 {next_state, active, LoopDat};
286active(release_complete, LoopDat) ->
287 {next_state, active, LoopDat};
288active(released, LoopDat) ->
289 % send N-DISCONNECT.ind to user
290 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
291 spec_name = indication}),
292 % release resources and local reference (freeze)
293 % stop inactivity timers
294 stop_inact_timers(LoopDat),
295 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200296 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100297 {next_state, idle, LoopDat};
298active(error, LoopDat) ->
299 % send N-DISCONNECT.ind to user
300 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
301 spec_name = indication}),
302 % release resources and local reference (freeze)
303 % stop inactivity timers
304 stop_inact_timers(LoopDat),
305 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200306 osmo_util:make_prim('OCRC', 'RELEASE COMPLETE', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100307 {next_state, idle, LoopDat};
308active(rcv_inact_tmr_exp, LoopDat) ->
309 disc_ind_stop_rel_3(LoopDat);
310active(routing_failure, LoopDat) ->
311 % send N-DISCONNECT.ind to user
312 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
313 spec_name = indication}),
314 % stop inactivity timers
315 stop_inact_timers(LoopDat),
316 % start release timer
317 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER};
318% Connection release procedures at destination node
319%active(internal_disconnect) ->
320% Data transfer procedures
Harald Welteda95baa2010-12-20 12:38:34 +0100321active(#primitive{subsystem = 'N', gen_name = 'DATA',
322 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100323 % FIXME Segment NSDU and assign value to bit M
324 % FIXME handle protocol class 3
325 gen_fsm:send_event(LoopDat#state.scrc_pid, {dt1, []}),
326 % restart send inactivity timer
327 LoopDat1 = restart_tx_inact_timer(LoopDat),
328 {next_state, active, LoopDat1};
Harald Welteda95baa2010-12-20 12:38:34 +0100329active(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION-MSG',
Harald Welte715b5f42010-12-20 14:10:05 +0100330 spec_name = indication, parameters = Msg}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100331 % 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
Harald Welte715b5f42010-12-20 14:10:05 +0100336 UserData = proplists:get_value(user_data, Msg#sccp_msg.parameters),
Harald Welte0f2f5962011-04-04 15:59:49 +0200337 send_user(LoopDat, osmo_util:make_prim('N', 'DATA', indication, {user_data, UserData})),
Harald Welte033cef02010-12-19 22:47:14 +0100338 {next_state, active, LoopDat1};
339% Reset procedures
Harald Welteda95baa2010-12-20 12:38:34 +0100340active(#primitive{subsystem = 'N', gen_name = 'RESET',
341 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100342 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200343 osmo_util:make_prim('OCRC', 'RESET', request, Param)),
Harald Welte033cef02010-12-19 22:47:14 +0100344 % start reset timer
345 % restart send inact timer
346 LoopDat1 = restart_tx_inact_timer(LoopDat),
347 % reset variables and discard all queued and unacked msgs
348 {next_state, reset_outgoing, LoopDat1, ?RESET_TIMER};
349active(internal_reset_req, LoopDat) ->
350 % N-RESET.ind to user
351 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
352 spec_name = indication}),
353 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200354 osmo_util:make_prim('OCRC', 'RESET', request)),
Harald Welte033cef02010-12-19 22:47:14 +0100355 % start reset timer
356 % restart send inact timer
357 LoopDat1 = restart_tx_inact_timer(LoopDat),
358 % reset variables and discard all queued and unacked msgs
359 {next_state, bothway_reset, LoopDat1, ?RESET_TIMER};
360active(reset_confirm, LoopDat) ->
361 % discard received message
362 {next_state, active, LoopDat};
363active(reset_req, LoopDat) ->
364 % restart send inactivity timer
365 LoopDat1 = restart_tx_inact_timer(LoopDat),
366 % N-RESET.ind to user
Harald Welte0f2f5962011-04-04 15:59:49 +0200367 send_user(LoopDat, osmo_util:make_prim('N', 'RESET', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100368 % reset variables and discard all queued and unacked msgs
369 {next_state, reset_incoming, LoopDat1}.
370
371rel_res_stop_tmr_12(LoopDat) ->
372 % release resources and local reference (freeze)
373 % stop release and interval timers
374 {next_state, idle, LoopDat}.
375
376% STATE Disconnect pending
377disconnect_pending(release_complete, LoopDat) ->
378 rel_res_stop_tmr_12(LoopDat);
379disconnect_pending(released_error, LoopDat) ->
380 rel_res_stop_tmr_12(LoopDat);
381disconnect_pending(routing_failure, LoopDat) ->
Harald Welte24302362010-12-20 12:39:17 +0100382 {next_state, disconnect_pending, LoopDat};
Harald Welte033cef02010-12-19 22:47:14 +0100383disconnect_pending(other_npdu_type, LoopDat) ->
384 % discared received message
Harald Welte24302362010-12-20 12:39:17 +0100385 {next_state, disconnect_pending, LoopDat};
Harald Welte033cef02010-12-19 22:47:14 +0100386disconnect_pending(timeout, LoopDat) ->
387 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200388 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100389 % start interval timer
390 % FIXME start repeat release timer
391 {next_state, disconnect_pending, ?RELEASE_REP_TIMER};
392disconnect_pending(intv_tmr_exp, LoopDat) ->
393 % inform maintenance
394 rel_res_stop_tmr_12(LoopDat);
395% FIXME: this is currently ending up in normal 'timeout' above
396disconnect_pending(repeat_release_tmr_exp, LoopDat) ->
397 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welte0f2f5962011-04-04 15:59:49 +0200398 osmo_util:make_prim('OCRC', 'RELEASED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100399 % FIXME restart repeat release timer
400 {next_state, disconnect_pending}.
401
402res_out_res_conf_req(LoopDat) ->
403 % N-RESET.conf to user
Harald Welte0f2f5962011-04-04 15:59:49 +0200404 send_user(LoopDat, osmo_util:make_prim('N', 'RESET', confirm)),
Harald Welte033cef02010-12-19 22:47:14 +0100405 % stop reset timer (implicit)
406 % restart receive inactivity timer
407 LoopDat1 = restart_rx_inact_timer(LoopDat),
408 % resume data transfer
409 {next_state, active, LoopDat1}.
410
411% STATE Reset outgoing
Harald Welteda95baa2010-12-20 12:38:34 +0100412reset_outgoing(#primitive{subsystem = 'N', gen_name = 'DATA',
413 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100414 % FIXME received information ?!?
415 {next_state, reset_outgoing, LoopDat};
Harald Welteda95baa2010-12-20 12:38:34 +0100416reset_outgoing(#primitive{subsystem = 'N', gen_name = 'EXPEDITED DATA',
417 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100418 % FIXME received information ?!?
419 {next_state, reset_outgoing, LoopDat};
420reset_outgoing(timeout, LoopDat) ->
421 % FIXME check for temporary connection section
422 % inform maintenance
423 {next_state, maintenance_Blocking, LoopDat};
424%reset_outgoing(error, LoopDat) ->
425%reset_outgoing(released, LoopDat) ->
426reset_outgoing(other_npdu_type, LoopDat) ->
427 % discard received message
428 {next_state, reset_outgoing, LoopDat};
429reset_outgoing(reset_confirm, LoopDat) ->
430 res_out_res_conf_req(LoopDat);
431reset_outgoing(reset_request, LoopDat) ->
432 res_out_res_conf_req(LoopDat).
433
434bway_res_req_resp(LoopDat) ->
435 {next_state, reset_outgoing, LoopDat}.
436
437bway_res_res_conf_req(LoopDat) ->
438 % N-RESET.conf to user
439 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
440 spec_name = confirm}),
441 % stop reset timer (implicit)
442 % restart receive inactivity timer
443 LoopDat1 = restart_rx_inact_timer(LoopDat),
444 {next_state, reset_incoming, LoopDat1}.
445
446% STATE Bothway Reset
Harald Welteda95baa2010-12-20 12:38:34 +0100447bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
448 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100449 bway_res_req_resp(LoopDat);
Harald Welteda95baa2010-12-20 12:38:34 +0100450bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
451 spec_name = response, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100452 bway_res_req_resp(LoopDat);
453bothway_reset(timeout, LoopDat) ->
454 % FIXME check for temporary connection section
455 % inform maintenance
456 {next_state, maintenance_Blocking, LoopDat};
457%bothway_reset(error, LoopDat) ->
458%bothway_reset(released, LoopDat) ->
459bothway_reset(other_npdu_type, LoopDat) ->
460 % discard received message
461 {next_state, bothway_reset, LoopDat}.
462
463% STATE Reset incoming
Harald Welteda95baa2010-12-20 12:38:34 +0100464reset_incoming(#primitive{subsystem = 'N', gen_name = 'RESET',
465 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100466 % received information
467 {nest_state, reset_incoming, LoopDat};
468%reset_incoming(error, LoopDat) ->
469%reset_incoming(released, LoopDat) ->
470reset_incoming(other_npdu_type, LoopDat) ->
471 % discard received message
472 % internal reset request
473 {next_state, active, LoopDat}.
474% FIXME: response or request
475%reset_incoming(