blob: 04b21654d66820c43aa6ad2e435d75bb99b072c0 [file] [log] [blame]
Harald Welteb6689882012-01-16 16:00:45 +01001% MTP2 Link State Control according to Q.703 Figure 3 / Figure 8
2
3% (C) 2011-2012 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/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
Harald Welteb6689882012-01-16 16:00:45 +010033
34-module(mtp2_lsc).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(gen_fsm).
37
38% gen_fsm exports
39-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
40
41% individual FSM states
42-export([power_off/2, out_of_service/2, initial_alignment/2,
43 aligned_not_ready/2, aligned_ready/2, in_service/2,
44 processor_outage/2]).
45
46% sync event handlers
47-export([power_off/3]).
48
49-record(lsc_state, {
50 t1_timeout,
51 t1,
52 iac_pid,
53 aerm_pid,
54 l3_pid,
55 poc_pid,
56 txc_pid,
Harald Welte9ebf3162012-01-20 02:02:25 +010057 rc_pid,
Harald Welteb6689882012-01-16 16:00:45 +010058 local_proc_out,
59 proc_out,
60 emergency
61 }).
62
63-define(M2PA_T1_DEF, 300000).
64
65%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
66% gen_fsm callbacks
67%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
68
Harald Welte9ebf3162012-01-20 02:02:25 +010069init([Aerm, Rc, Txc, L3, Poc]) ->
Harald Welteb6689882012-01-16 16:00:45 +010070 {ok, Iac} = gen_fsm:start_link(mtp2_iac, [self(), Aerm, Txc], [{debug, [trace]}]),
71 LscState = #lsc_state{t1_timeout = ?M2PA_T1_DEF,
72 iac_pid = Iac,
73 aerm_pid = Aerm,
74 l3_pid = L3,
75 poc_pid = L3,
76 txc_pid = Txc,
Harald Welte9ebf3162012-01-20 02:02:25 +010077 rc_pid = Rc,
Harald Welteb6689882012-01-16 16:00:45 +010078 local_proc_out = 0,
79 proc_out = 0,
80 emergency = 0},
81 {ok, power_off, LscState}.
82
83terminate(Reason, State, _LoopDat) ->
84 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
85 [?MODULE, State, Reason]),
86 ok.
87
88code_change(_OldVsn, StateName, LoopDat, _Extra) ->
89 {ok, StateName, LoopDat}.
90
91handle_event(Event, State, LoopDat) ->
92 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
93 {next_state, State, LoopDat}.
94
95
96handle_info(Info, State, LoopDat) ->
97 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
98 {next_state, State, LoopDat}.
99
100
101
102%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
103% STATE: power_off
104%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
105
106power_off(power_on, LoopDat) ->
107 % Power On from MGMT
108 send_to(txc, start, LoopDat),
109 send_to(txc, si_os, LoopDat),
110 send_to(aerm, set_ti_to_tin, LoopDat),
111 % Cancel local processor outage, cancel emergency
112 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}.
113
114power_off(get_iac_pid, From, LoopDat) ->
115 Iac = LoopDat#lsc_state.iac_pid,
116 {reply, {ok, Iac}, power_off, LoopDat}.
117
118
119%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
120% STATE: out_of_service
121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
122
123out_of_service(start, LoopDat) ->
124 % Start from L3
125 send_to(rc, start, LoopDat),
126 send_to(txc, start, LoopDat),
127 case LoopDat#lsc_state.emergency of
128 1 ->
129 send_to(iac, emergency, LoopDat);
130 _ ->
131 ok
132 end,
133 send_to(iac, start, LoopDat),
134 {next_state, initial_alignment, LoopDat};
135
136out_of_service(retrieve_bsnt, LoopDat) ->
137 send_to(rc, retrieve_bsnt, LoopDat),
138 {next_state, out_of_service, LoopDat};
139
140out_of_service(retrieval_request_and_fsnc, LoopDat) ->
141 send_to(txc, retrieval_request_and_fsnc, LoopDat),
142 {next_state, out_of_service, LoopDat};
143
144out_of_service(emergency, LoopDat) ->
145 {next_state, out_of_service, LoopDat#lsc_state{emergency=1}};
146
147out_of_service(emergency_ceases, LoopDat) ->
148 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
149
150out_of_service(What, LoopDat) when What == local_processor_outage;
151 What == level3_failure ->
152 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=1}};
153
Harald Weltee5014372012-01-19 23:19:34 +0100154out_of_service(si_os, LoopDat) ->
155 % this transition is not specified in Q.703, but it makes
156 % quite a bit of sense. yate M2PA requires it, too.
157 {next_state, out_of_service, LoopDat};
158
Harald Welteb6689882012-01-16 16:00:45 +0100159out_of_service(local_processor_recovered, LoopDat) ->
160 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0}}.
161
162
163%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
164% STATE: initial_alignment
165%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
166
167initial_alignment(What, LoopDat) when What == local_processor_outage;
168 What == level3_failure ->
169 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=1}};
170
171initial_alignment(local_processor_recovered, LoopDat) ->
172 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=0}};
173
174initial_alignment(emergency, LoopDat) ->
175 send_to(iac, emergency, LoopDat),
176 {next_state, initial_alignment, LoopDat#lsc_state{emergency=1}};
177
178initial_alignment(alignment_complete, LoopDat) ->
179 send_to(suerm, start, LoopDat),
180 {ok, T1} = timer:apply_after(LoopDat#lsc_state.t1_timeout,
181 gen_fsm, send_event,
182 [self(), {timer_expired, t1}]),
183 case LoopDat#lsc_state.local_proc_out of
184 1 ->
185 send_to(poc, local_processor_outage, LoopDat),
186 send_to(txc, si_po, LoopDat),
Harald Welte9ebf3162012-01-20 02:02:25 +0100187 send_to(rc, reject_msu_fisu, LoopDat),
Harald Welteb6689882012-01-16 16:00:45 +0100188 NextState = aligned_not_ready;
189 _ ->
190 send_to(txc, fisu, LoopDat),
Harald Welte9ebf3162012-01-20 02:02:25 +0100191 send_to(rc, accept_msu_fisu, LoopDat),
Harald Welteb6689882012-01-16 16:00:45 +0100192 NextState = aligned_ready
193 end,
194 {next_state, NextState, LoopDat#lsc_state{t1=T1}};
195
196initial_alignment(stop, LoopDat) ->
197 send_to(iac, stop, LoopDat),
198 send_to(rc, stop, LoopDat),
199 send_to(txc, si_os, LoopDat),
200 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
201
202initial_alignment(link_failure, LoopDat) ->
203 send_to(l3, out_of_service, LoopDat),
204 send_to(iac, stop, LoopDat),
205 send_to(rc, stop, LoopDat),
206 send_to(txc, si_os, LoopDat),
207 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
208
209initial_alignment(alignment_not_possible, LoopDat) ->
210 send_to(rc, stop, LoopDat),
211 send_to(txc, si_os, LoopDat),
212 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
213
Harald Welte70984972012-01-19 22:50:39 +0100214% forward into IAC sub-state-machine
Harald Welteb6689882012-01-16 16:00:45 +0100215initial_alignment(What, LoopDat) when
Harald Welte70984972012-01-19 22:50:39 +0100216 What == si_n; What == si_e; What == si_o; What == si_os;
217 What == fisu_msu_received ->
218 Iac = LoopDat#lsc_state.iac_pid,
219 gen_fsm:send_event(Iac, What),
Harald Welteb6689882012-01-16 16:00:45 +0100220 {next_state, initial_alignment, LoopDat}.
221
222
223%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
224% STATE: aligned_ready
225%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
226
227aligned_ready(SioOrSios, LoopDat) when SioOrSios == si_o;
228 SioOrSios == si_os;
229 SioOrSios == link_failure ->
230 timer:cancel(LoopDat#lsc_state.t1),
231 send_to(l3, out_of_service, LoopDat),
232 send_to(rc, stop, LoopDat),
233 send_to(suerm, stop, LoopDat),
234 send_to(txc, si_os, LoopDat),
235 {next_state, out_of_service, LoopDat};
236
237aligned_ready(stop, LoopDat) ->
238 timer:cancel(LoopDat#lsc_state.t1),
239 send_to(rc, stop, LoopDat),
240 send_to(suerm, stop, LoopDat),
241 send_to(txc, si_os, LoopDat),
242 {next_state, out_of_service, LoopDat};
243
244aligned_ready({timer_expired, t1}, LoopDat) ->
245 send_to(l3, out_of_service, LoopDat),
246 send_to(rc, stop, LoopDat),
247 send_to(suerm, stop, LoopDat),
248 send_to(txc, si_os, LoopDat),
249 {next_state, out_of_service, LoopDat};
250
251aligned_ready(si_po, LoopDat) ->
252 timer:cancel(LoopDat#lsc_state.t1),
253 send_to(l3, remote_processor_outage, LoopDat),
254 send_to(poc, remote_processor_outage, LoopDat),
255 {next_state, processor_outage, LoopDat};
256
257aligned_ready(fisu_msu_received, LoopDat) ->
258 send_to(l3, in_service, LoopDat),
259 timer:cancel(LoopDat#lsc_state.t1),
260 send_to(txc, msu, LoopDat),
261 {next_state, in_service, LoopDat};
262aligned_ready(What, LoopDat) when What == local_processor_outage;
263 What == level3_failure ->
264 send_to(poc, local_processor_outage, LoopDat),
265 send_to(txc, si_po, LoopDat),
Harald Welte9ebf3162012-01-20 02:02:25 +0100266 send_to(rc, reject_msu_fisu, LoopDat),
Harald Welteb6689882012-01-16 16:00:45 +0100267 {next_state, aligned_not_ready, LoopDat}.
268
269
270%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
271% STATE: aligned_not_ready
272%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
273
274aligned_not_ready(Err, LoopDat) when Err == link_failure;
275 Err == si_o;
276 Err == si_os ->
277 timer:cancel(LoopDat#lsc_state.t1),
278 send_to(l3, out_of_service, LoopDat),
279 send_to(l3, stop, LoopDat),
280 send_to(suerm, stop, LoopDat),
281 send_to(txc, si_os, LoopDat),
282 send_to(poc, stop, LoopDat),
283 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
284
285aligned_not_ready(stop, LoopDat) ->
286 timer:cancel(LoopDat#lsc_state.t1),
287 send_to(l3, stop, LoopDat),
288 send_to(suerm, stop, LoopDat),
289 send_to(txc, si_os, LoopDat),
290 send_to(poc, stop, LoopDat),
291 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
292
293aligned_not_ready({timer_expired, t1}, LoopDat) ->
294 send_to(l3, stop, LoopDat),
295 send_to(suerm, stop, LoopDat),
296 send_to(txc, si_os, LoopDat),
297 send_to(poc, stop, LoopDat),
298 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
299
300aligned_not_ready(local_processor_recovered, LoopDat) ->
301 send_to(poc, local_processor_recovered, LoopDat),
302 send_to(txc, fisu, LoopDat),
303 send_to(rc, accept_msu_fisu, LoopDat),
304 {next_state, aligned_ready, LoopDat#lsc_state{local_proc_out=0}};
305
306aligned_not_ready(fisu_msu_received, LoopDat) ->
307 send_to(l3, in_service, LoopDat),
308 timer:cancel(LoopDat#lsc_state.t1),
309 {next_state, processor_outage, LoopDat};
310
311aligned_not_ready(si_po, LoopDat) ->
312 send_to(l3, remote_processor_outage, LoopDat),
313 send_to(poc, remote_processor_outage, LoopDat),
314 timer:cancel(LoopDat#lsc_state.t1),
315 {next_state, processor_outage, LoopDat}.
316
317
318%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
319% STATE: in_service
320%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
321
322in_service(What, LoopDat) when What == link_failure;
323 What == si_o;
324 What == si_n;
325 What == si_e;
326 What == si_os ->
327 send_to(l3, out_of_service, LoopDat),
328 send_to(suerm, stop, LoopDat),
329 send_to(rc, stop, LoopDat),
330 send_to(txc, si_os, LoopDat),
331 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
332
333in_service(stop, LoopDat) ->
334 send_to(suerm, stop, LoopDat),
335 send_to(rc, stop, LoopDat),
336 send_to(txc, si_os, LoopDat),
337 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
338
339in_service(What, LoopDat) when What == local_processor_outage;
340 What == level3_failure ->
341 send_to(poc, local_processor_outage, LoopDat),
342 send_to(txc, si_po, LoopDat),
343 send_to(rc, reject_msu_fisu, LoopDat),
344 {next_state, aligned_not_ready, LoopDat#lsc_state{local_proc_out=1}};
345
346in_service(si_po, LoopDat) ->
347 send_to(txc, fisu, LoopDat),
348 send_to(l3, remote_processor_outage, LoopDat),
349 send_to(poc, remote_processor_outage, LoopDat),
350 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}.
351
352
353%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
354% STATE: processor_outage
355%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
356
357processor_outage(retrieval_request_and_fsnc, LoopDat) ->
358 send_to(txc, retrieval_request_and_fsnc, LoopDat),
359 {next_state, processor_outage, LoopDat};
360
361processor_outage(fisu_msu_received, LoopDat) ->
362 send_to(poc, remote_processor_recovered, LoopDat),
363 send_to(l3, remote_processor_recovered, LoopDat),
364 {next_state, processor_outage, LoopDat};
365
366processor_outage(retrieve_bsnt, LoopDat) ->
367 send_to(rc, retrieve_bsnt, LoopDat),
368 {next_state, processor_outage, LoopDat};
369
370processor_outage(What, LoopDat) when What == local_processor_outage;
371 What == level3_failure ->
372 send_to(poc, local_processor_outage, LoopDat),
373 send_to(txc, si_po, LoopDat),
374 {next_state, processor_outage, LoopDat#lsc_state{local_proc_out=1}};
375
376processor_outage(si_po, LoopDat) ->
377 send_to(l3, remote_processor_outage, LoopDat),
378 send_to(poc, remote_processor_outage, LoopDat),
379 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}};
380
381processor_outage(local_processor_recovered, LoopDat) ->
382 send_to(poc, local_processor_recovered, LoopDat),
383 send_to(rc, retrieve_fsnx, LoopDat),
384 send_to(txc, fisu, LoopDat),
385 {next_state, processor_outage, LoopDat};
386
387processor_outage(flush_buffers, LoopDat) ->
388 send_to(txc, flush_buffers, LoopDat),
389 % FIXME: mark L3 ind recv
390 {next_state, processor_outage, LoopDat};
391
392processor_outage(no_processor_outage, LoopDat) ->
393 % FIXME: check L3 ind
394 send_to(txc, msu, LoopDat),
395 send_to(rc, accept_msu_fisu, LoopDat),
396 {next_state, in_service, LoopDat#lsc_state{local_proc_out=0, proc_out=0}};
397
398processor_outage(What, LoopDat) when What == link_failure;
399 What == si_o;
400 What == si_n;
401 What == si_e;
402 What == si_os ->
403 send_to(l3, out_of_service, LoopDat),
404 send_to(suerm, stop, LoopDat),
405 send_to(rc, stop, LoopDat),
406 send_to(poc, stop, LoopDat),
407 send_to(txc, si_os, LoopDat),
408 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}};
409
410processor_outage(stop, LoopDat) ->
411 send_to(suerm, stop, LoopDat),
412 send_to(rc, stop, LoopDat),
413 send_to(poc, stop, LoopDat),
414 send_to(txc, si_os, LoopDat),
415 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}.
416
417
418
419%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
420% helper functions
421%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
422send_to(txc, What, #lsc_state{txc_pid = Txc}) ->
423 Txc ! {lsc_txc, What};
424send_to(iac, What, #lsc_state{iac_pid = Iac}) ->
425 gen_fsm:send_event(Iac, What);
Harald Welte9ebf3162012-01-20 02:02:25 +0100426send_to(rc, What, #lsc_state{rc_pid = Rc}) ->
427 Rc ! {lsc_rc, What};
Harald Welteb6689882012-01-16 16:00:45 +0100428send_to(Who, What, _LoopDat) ->
429 io:format("Not sending LSC -> ~p: ~p~n", [Who, What]).
430