blob: 181287fa461eb872ff86c0cfc0227e289de8f53a [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
Harald Weltefba08e42010-12-20 12:40:00 +010078 io:format("T(ias) is expired, send IT message~n", []),
79 #state{local_reference = LocRef, remote_reference = RemRef,
80 class = Class} = LoopDat,
81 Params = [{dst_local_ref, RemRef},{src_local_ref, LocRef},
82 {protocol_class, Class}, {seq_segm, 0}, {credit, 0}],
83 Msg = #sccp_msg{msg_type = ?SCCP_MSGT_IT, parameters = Params},
84 gen_fsm:send_event(LoopDat#state.scrc_pid,
85 make_prim('OCRC','CONNECTION-MSG', request, Msg)),
Harald Welte033cef02010-12-19 22:47:14 +010086 {next_state, State, LoopDat};
87handle_event({timer_expired, rx_inact_timer}, State, LoopDat) ->
88 io:format("FIXME: T(iar) is expired, release connection~n", []),
89 % FIXME: Initiate connection release procedure
90 {next_state, State, LoopDat}.
91
92% helper function to create a #primitive record
93make_prim(Subsys, GenName, SpecName) ->
94 make_prim(Subsys, GenName, SpecName, []).
95make_prim(Subsys, GenName, SpecName, Param) ->
96 #primitive{subsystem = Subsys, gen_name = GenName,
97 spec_name = SpecName, parameters = Param}.
98
99% helper function to send a primitive to the user
Harald Welteda95baa2010-12-20 12:38:34 +0100100send_user(_LoopDat = #state{user_pid = Pid}, Prim = #primitive{}) ->
Harald Welte033cef02010-12-19 22:47:14 +0100101 Pid ! {sccp, Prim}.
102
103% low-level functions regarding activity timers
104restart_tx_inact_timer(LoopDat) ->
105 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
106 [self(), {timer_expired, tx_inact_timer}]),
107 LoopDat#state{tx_inact_timer = Tias}.
108
109restart_rx_inact_timer(LoopDat) ->
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}.
113
114start_inact_timers(LoopDat) ->
115 Tias = timer:apply_after(?TX_INACT_TIMER, gen_fsm, send_all_state_event,
116 [self(), {timer_expired, tx_inact_timer}]),
117 Tiar = timer:apply_after(?RX_INACT_TIMER, gen_fsm, send_all_state_event,
118 [self(), {timer_expired, rx_inact_timer}]),
119 LoopDat#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}.
120
Harald Welteda95baa2010-12-20 12:38:34 +0100121stop_inact_timers(#state{rx_inact_timer = Tiar, tx_inact_timer = Tias}) ->
Harald Welte033cef02010-12-19 22:47:14 +0100122 timer:cancel(Tiar),
123 timer:cancel(Tias).
124
125
126% -spec idle(#primitive{} | ) -> gen_fsm_state_return().
127
128% STATE Idle
129
130% N-CONNECT.req from user
Harald Welteda95baa2010-12-20 12:38:34 +0100131idle(#primitive{subsystem = 'N', gen_name = 'CONNECT',
132 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100133 % assign local reference and SLS
134 % determine protocol class and credit
135 LoopDat1 = LoopDat#state{local_reference = make_ref(), class = 2},
136 gen_fsm:send_event(LoopDat1#state.scrc_pid,
137 make_prim('OCRC','CONNECTION', indication, Param)),
138 % start connection timer
139 {next_state, conn_pend_out, LoopDat1, ?CONNECTION_TIMER};
140
141% RCOC-CONNECTION.req from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100142idle(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION',
143 spec_name = indication, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100144 % associate remote reference to connection section
145 RemRef = proplists:get_value(src_local_ref, Params),
146 % determine protocol class and FIXME: credit
147 Class = proplists:get_value(protocol_class, Params),
148 LoopDat1 = LoopDat#state{remote_reference = RemRef, class = Class},
149 % send N-CONNECT.ind to user
150 send_user(LoopDat1, make_prim('N', 'CONNECT', indication, [{scoc_pid, self()}|Params])),
151 %#primitive{subsystem = 'N', gen_name = 'CONNECT', spec_name = indication}
152 {next_state, conn_pend_in, LoopDat1};
153
154% RCOC-ROUTING_FAILURE.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100155idle(#primitive{subsystem = 'RCOC', gen_name = 'ROUTING FAILURE',
156 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100157 gen_fsm:send_event(LoopDat#state.scrc_pid,
158 make_prim('OCRC', 'CONNECTION REFUSED', indication)),
159 {next_state, idle, LoopDat};
160
161%FIXME: request type 2 ?!?
162
163% RCOC-RELEASED.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100164idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASED',
165 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100166 gen_fsm:send_event(LoopDat#state.scrc_pid,
167 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
168 {next_state, idle, LoopDat};
169
170% RCOC-RELEASE_COMPLETE.ind from SCRC
Harald Welteda95baa2010-12-20 12:38:34 +0100171idle(#primitive{subsystem = 'RCOC', gen_name = 'RELEASE COMPLETE',
172 spec_name = indication}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100173 {next_state, idle, LoopDat};
174
175idle(#primitive{subsystem= 'RCOC', gen_name = 'DATA',
176 spec_name = indication, parameters = Param}, LoopDat) ->
177 % FIXME: if source reference, send error
178 send_user(LoopDat, make_prim('N', 'DATA', indication, Param)),
179 {next_state, idle, LoopDat}.
180
181% STATE Connection pending incoming
Harald Welteda95baa2010-12-20 12:38:34 +0100182conn_pend_in(#primitive{subsystem = 'N', gen_name = 'CONNECT',
183 spec_name = response, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100184 io:format("SCOC N-CONNECT.resp LoopDat ~p~n", [LoopDat]),
185 % assign local reference, SLS, protocol class and credit for inc section
186 OutParam = [{dst_local_ref, LoopDat#state.remote_reference},
187 {src_local_ref, LoopDat#state.local_reference},
188 {protocol_class, LoopDat#state.class}] ++ Param,
189 gen_fsm:send_event(LoopDat#state.scrc_pid,
190 make_prim('OCRC', 'CONNECTION', confirm, OutParam)),
191 % start inactivity timers
192 LoopDat1 = start_inact_timers(LoopDat),
193 {next_state, active, LoopDat1};
194conn_pend_in(any_npdu_type, LoopDat) ->
195 {next_state, conn_pend_in, LoopDat};
Harald Welteda95baa2010-12-20 12:38:34 +0100196conn_pend_in(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
197 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100198 % release resourcers (local ref may have to be released an frozen)
199 gen_fsm:send_event(LoopDat#state.scrc_pid,
200 make_prim('OCRC', 'CONNECTION REFUSED', indication, Param)),
201 {next_state, idle, LoopDat}.
202
203
204disc_ind_stop_rel_3(LoopDat) ->
205 % send N-DISCONNECT.ind to user
206 send_user(LoopDat, make_prim('N', 'DISCONNECT',indication)),
207 % stop inactivity timers
208 stop_inact_timers(LoopDat),
209 gen_fsm:send_event(LoopDat#state.scrc_pid,
Harald Welteda95baa2010-12-20 12:38:34 +0100210 make_prim('OCRC', 'RELEASED', indication)),
Harald Welte033cef02010-12-19 22:47:14 +0100211 % start release timer
212 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
213
214rel_res_disc_ind_idle_2(LoopDat) ->
215 % release resources and local reference (freeze)
216 % send N-DISCONNECT.ind to user
217 send_user(LoopDat, make_prim('N', 'DISCONNECT', indication)),
218 {next_state, idle, LoopDat}.
219
220
221% STATE Connection pending outgoing
Harald Welteda95baa2010-12-20 12:38:34 +0100222conn_pend_out(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
223 spec_name = request}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100224 % FIXME: what about the connection timer ?
225 {next_state, wait_conn_conf, LoopDat};
226conn_pend_out(timeout, LoopDat) ->
227 rel_res_disc_ind_idle_2(LoopDat);
228conn_pend_out(routing_failure, LoopDat) ->
229 rel_res_disc_ind_idle_2(LoopDat);
230conn_pend_out(released, LoopDat) ->
231 gen_fsm:send_event(LoopDat#state.scrc_pid,
232 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
233 rel_res_disc_ind_idle_2(LoopDat);
234% other N-PDU Type
235conn_pend_out(other_npdu_type, LoopDat) ->
236 rel_res_disc_ind_idle_2(LoopDat);
237conn_pend_out(connection_refused, LoopDat) ->
238 rel_res_disc_ind_idle_2(LoopDat);
239conn_pend_out(connection_confirm, LoopDat) ->
240 % start inactivity timers
241 LoopDat1 = start_inact_timers(LoopDat),
242 % assign protocol class and associate remote reference to connection
243 % send N-CONNECT.conf to user
244 send_user(LoopDat1, #primitive{subsystem = 'N', gen_name = 'CONNECT',
245 spec_name = confirm}),
246 {next_state, active, LoopDat1}.
247
248stop_c_tmr_rel_idle_5(LoopDat) ->
249 % stop connection timer (implicit)
250 % release resources and local reference
251 {next_state, idle, LoopDat}.
252
253rel_freeze_idle(LoopDat) ->
254 {next_state, idle, LoopDat}.
255
256% STATE Wait connection confirmed
257wait_conn_conf(released, LoopDat) ->
258 gen_fsm:send_event(LoopDat#state.scrc_pid,
259 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
260 stop_c_tmr_rel_idle_5(LoopDat);
261wait_conn_conf(connection_confirm, LoopDat) ->
262 % stop connection timer (implicit)
263 % associate remote reference to connection
264 relsd_tmr_disc_pend_6(LoopDat);
265wait_conn_conf(other_npdu_type, LoopDat) ->
266 % stop connection timer (implicit)
267 rel_freeze_idle(LoopDat);
268wait_conn_conf(timeout, LoopDat) ->
269 stop_c_tmr_rel_idle_5(LoopDat);
270wait_conn_conf(connection_refused, LoopDat) ->
271 stop_c_tmr_rel_idle_5(LoopDat);
272wait_conn_conf(routing_failure, LoopDat) ->
273 stop_c_tmr_rel_idle_5(LoopDat).
274
275
276relsd_tmr_disc_pend_6(LoopDat) ->
277 gen_fsm:send_event(LoopDat#state.scrc_pid,
278 make_prim('OCRC', 'RELEASED', indication)),
279 % start release timer
280 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER}.
281
282% STATE Active
Harald Welteda95baa2010-12-20 12:38:34 +0100283active(#primitive{subsystem = 'N', gen_name = 'DISCONNECT',
284 spec_name = request}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100285 % stop inactivity timers
286 start_inact_timers(LoopDat),
287 relsd_tmr_disc_pend_6(LoopDat);
288active(internal_disconnect, LoopDat) ->
289 disc_ind_stop_rel_3(LoopDat);
290active(connection_refused, LoopDat) ->
291 {next_state, active, LoopDat};
292active(connection_confirm, LoopDat) ->
293 {next_state, active, LoopDat};
294active(release_complete, LoopDat) ->
295 {next_state, active, LoopDat};
296active(released, LoopDat) ->
297 % send N-DISCONNECT.ind to user
298 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
299 spec_name = indication}),
300 % release resources and local reference (freeze)
301 % stop inactivity timers
302 stop_inact_timers(LoopDat),
303 gen_fsm:send_event(LoopDat#state.scrc_pid,
304 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
305 {next_state, idle, LoopDat};
306active(error, LoopDat) ->
307 % send N-DISCONNECT.ind to user
308 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
309 spec_name = indication}),
310 % release resources and local reference (freeze)
311 % stop inactivity timers
312 stop_inact_timers(LoopDat),
313 gen_fsm:send_event(LoopDat#state.scrc_pid,
314 make_prim('OCRC', 'RELEASE COMPLETE', indication)),
315 {next_state, idle, LoopDat};
316active(rcv_inact_tmr_exp, LoopDat) ->
317 disc_ind_stop_rel_3(LoopDat);
318active(routing_failure, LoopDat) ->
319 % send N-DISCONNECT.ind to user
320 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'DISCONNECT',
321 spec_name = indication}),
322 % stop inactivity timers
323 stop_inact_timers(LoopDat),
324 % start release timer
325 {next_state, disconnect_pending, LoopDat, ?RELEASE_TIMER};
326% Connection release procedures at destination node
327%active(internal_disconnect) ->
328% Data transfer procedures
Harald Welteda95baa2010-12-20 12:38:34 +0100329active(#primitive{subsystem = 'N', gen_name = 'DATA',
330 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100331 % FIXME Segment NSDU and assign value to bit M
332 % FIXME handle protocol class 3
333 gen_fsm:send_event(LoopDat#state.scrc_pid, {dt1, []}),
334 % restart send inactivity timer
335 LoopDat1 = restart_tx_inact_timer(LoopDat),
336 {next_state, active, LoopDat1};
Harald Welteda95baa2010-12-20 12:38:34 +0100337active(#primitive{subsystem = 'RCOC', gen_name = 'CONNECTION-MSG',
Harald Welte715b5f42010-12-20 14:10:05 +0100338 spec_name = indication, parameters = Msg}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100339 % restart receive inactivity timer
340 LoopDat1 = restart_rx_inact_timer(LoopDat),
341 % FIXME handle protocol class 3
342 % FIXME check for M-bit=1 and put data in Rx queue
343 % N-DATA.ind to user
Harald Welte715b5f42010-12-20 14:10:05 +0100344 UserData = proplists:get_value(user_data, Msg#sccp_msg.parameters),
Harald Welteda95baa2010-12-20 12:38:34 +0100345 send_user(LoopDat, make_prim('N', 'DATA', indication, {user_data, UserData})),
Harald Welte033cef02010-12-19 22:47:14 +0100346 {next_state, active, LoopDat1};
347% Reset procedures
Harald Welteda95baa2010-12-20 12:38:34 +0100348active(#primitive{subsystem = 'N', gen_name = 'RESET',
349 spec_name = request, parameters = Param}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100350 gen_fsm:send_event(LoopDat#state.scrc_pid,
351 make_prim('OCRC', 'RESET', request, Param)),
352 % start reset timer
353 % restart send inact timer
354 LoopDat1 = restart_tx_inact_timer(LoopDat),
355 % reset variables and discard all queued and unacked msgs
356 {next_state, reset_outgoing, LoopDat1, ?RESET_TIMER};
357active(internal_reset_req, LoopDat) ->
358 % N-RESET.ind to user
359 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
360 spec_name = indication}),
361 gen_fsm:send_event(LoopDat#state.scrc_pid,
362 make_prim('OCRC', 'RESET', request)),
363 % start reset timer
364 % restart send inact timer
365 LoopDat1 = restart_tx_inact_timer(LoopDat),
366 % reset variables and discard all queued and unacked msgs
367 {next_state, bothway_reset, LoopDat1, ?RESET_TIMER};
368active(reset_confirm, LoopDat) ->
369 % discard received message
370 {next_state, active, LoopDat};
371active(reset_req, LoopDat) ->
372 % restart send inactivity timer
373 LoopDat1 = restart_tx_inact_timer(LoopDat),
374 % N-RESET.ind to user
375 send_user(LoopDat, make_prim('N', 'RESET', indication)),
376 % reset variables and discard all queued and unacked msgs
377 {next_state, reset_incoming, LoopDat1}.
378
379rel_res_stop_tmr_12(LoopDat) ->
380 % release resources and local reference (freeze)
381 % stop release and interval timers
382 {next_state, idle, LoopDat}.
383
384% STATE Disconnect pending
385disconnect_pending(release_complete, LoopDat) ->
386 rel_res_stop_tmr_12(LoopDat);
387disconnect_pending(released_error, LoopDat) ->
388 rel_res_stop_tmr_12(LoopDat);
389disconnect_pending(routing_failure, LoopDat) ->
Harald Welte24302362010-12-20 12:39:17 +0100390 {next_state, disconnect_pending, LoopDat};
Harald Welte033cef02010-12-19 22:47:14 +0100391disconnect_pending(other_npdu_type, LoopDat) ->
392 % discared received message
Harald Welte24302362010-12-20 12:39:17 +0100393 {next_state, disconnect_pending, LoopDat};
Harald Welte033cef02010-12-19 22:47:14 +0100394disconnect_pending(timeout, LoopDat) ->
395 gen_fsm:send_event(LoopDat#state.scrc_pid,
396 make_prim('OCRC', 'RELEASED', indication)),
397 % start interval timer
398 % FIXME start repeat release timer
399 {next_state, disconnect_pending, ?RELEASE_REP_TIMER};
400disconnect_pending(intv_tmr_exp, LoopDat) ->
401 % inform maintenance
402 rel_res_stop_tmr_12(LoopDat);
403% FIXME: this is currently ending up in normal 'timeout' above
404disconnect_pending(repeat_release_tmr_exp, LoopDat) ->
405 gen_fsm:send_event(LoopDat#state.scrc_pid,
406 make_prim('OCRC', 'RELEASED', indication)),
407 % FIXME restart repeat release timer
408 {next_state, disconnect_pending}.
409
410res_out_res_conf_req(LoopDat) ->
411 % N-RESET.conf to user
412 send_user(LoopDat, make_prim('N', 'RESET', confirm)),
413 % stop reset timer (implicit)
414 % restart receive inactivity timer
415 LoopDat1 = restart_rx_inact_timer(LoopDat),
416 % resume data transfer
417 {next_state, active, LoopDat1}.
418
419% STATE Reset outgoing
Harald Welteda95baa2010-12-20 12:38:34 +0100420reset_outgoing(#primitive{subsystem = 'N', gen_name = 'DATA',
421 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100422 % FIXME received information ?!?
423 {next_state, reset_outgoing, LoopDat};
Harald Welteda95baa2010-12-20 12:38:34 +0100424reset_outgoing(#primitive{subsystem = 'N', gen_name = 'EXPEDITED DATA',
425 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100426 % FIXME received information ?!?
427 {next_state, reset_outgoing, LoopDat};
428reset_outgoing(timeout, LoopDat) ->
429 % FIXME check for temporary connection section
430 % inform maintenance
431 {next_state, maintenance_Blocking, LoopDat};
432%reset_outgoing(error, LoopDat) ->
433%reset_outgoing(released, LoopDat) ->
434reset_outgoing(other_npdu_type, LoopDat) ->
435 % discard received message
436 {next_state, reset_outgoing, LoopDat};
437reset_outgoing(reset_confirm, LoopDat) ->
438 res_out_res_conf_req(LoopDat);
439reset_outgoing(reset_request, LoopDat) ->
440 res_out_res_conf_req(LoopDat).
441
442bway_res_req_resp(LoopDat) ->
443 {next_state, reset_outgoing, LoopDat}.
444
445bway_res_res_conf_req(LoopDat) ->
446 % N-RESET.conf to user
447 send_user(LoopDat, #primitive{subsystem = 'N', gen_name = 'RESET',
448 spec_name = confirm}),
449 % stop reset timer (implicit)
450 % restart receive inactivity timer
451 LoopDat1 = restart_rx_inact_timer(LoopDat),
452 {next_state, reset_incoming, LoopDat1}.
453
454% STATE Bothway Reset
Harald Welteda95baa2010-12-20 12:38:34 +0100455bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
456 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100457 bway_res_req_resp(LoopDat);
Harald Welteda95baa2010-12-20 12:38:34 +0100458bothway_reset(#primitive{subsystem = 'N', gen_name = 'RESET',
459 spec_name = response, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100460 bway_res_req_resp(LoopDat);
461bothway_reset(timeout, LoopDat) ->
462 % FIXME check for temporary connection section
463 % inform maintenance
464 {next_state, maintenance_Blocking, LoopDat};
465%bothway_reset(error, LoopDat) ->
466%bothway_reset(released, LoopDat) ->
467bothway_reset(other_npdu_type, LoopDat) ->
468 % discard received message
469 {next_state, bothway_reset, LoopDat}.
470
471% STATE Reset incoming
Harald Welteda95baa2010-12-20 12:38:34 +0100472reset_incoming(#primitive{subsystem = 'N', gen_name = 'RESET',
473 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welte033cef02010-12-19 22:47:14 +0100474 % received information
475 {nest_state, reset_incoming, LoopDat};
476%reset_incoming(error, LoopDat) ->
477%reset_incoming(released, LoopDat) ->
478reset_incoming(other_npdu_type, LoopDat) ->
479 % discard received message
480 % internal reset request
481 {next_state, active, LoopDat}.
482% FIXME: response or request
483%reset_incoming(