blob: 3cdf59a2e597e831ef912758aea6243e5ff38ba7 [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/>.
19
20-module(mtp2_lsc).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behaviour(gen_fsm).
23
24% gen_fsm exports
25-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
26
27% individual FSM states
28-export([power_off/2, out_of_service/2, initial_alignment/2,
29 aligned_not_ready/2, aligned_ready/2, in_service/2,
30 processor_outage/2]).
31
32% sync event handlers
33-export([power_off/3]).
34
35-record(lsc_state, {
36 t1_timeout,
37 t1,
38 iac_pid,
39 aerm_pid,
40 l3_pid,
41 poc_pid,
42 txc_pid,
43 local_proc_out,
44 proc_out,
45 emergency
46 }).
47
48-define(M2PA_T1_DEF, 300000).
49
50%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
51% gen_fsm callbacks
52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
53
54init([Aerm, Txc, L3, Poc]) ->
55 {ok, Iac} = gen_fsm:start_link(mtp2_iac, [self(), Aerm, Txc], [{debug, [trace]}]),
56 LscState = #lsc_state{t1_timeout = ?M2PA_T1_DEF,
57 iac_pid = Iac,
58 aerm_pid = Aerm,
59 l3_pid = L3,
60 poc_pid = L3,
61 txc_pid = Txc,
62 local_proc_out = 0,
63 proc_out = 0,
64 emergency = 0},
65 {ok, power_off, LscState}.
66
67terminate(Reason, State, _LoopDat) ->
68 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
69 [?MODULE, State, Reason]),
70 ok.
71
72code_change(_OldVsn, StateName, LoopDat, _Extra) ->
73 {ok, StateName, LoopDat}.
74
75handle_event(Event, State, LoopDat) ->
76 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
77 {next_state, State, LoopDat}.
78
79
80handle_info(Info, State, LoopDat) ->
81 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
82 {next_state, State, LoopDat}.
83
84
85
86%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
87% STATE: power_off
88%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
89
90power_off(power_on, LoopDat) ->
91 % Power On from MGMT
92 send_to(txc, start, LoopDat),
93 send_to(txc, si_os, LoopDat),
94 send_to(aerm, set_ti_to_tin, LoopDat),
95 % Cancel local processor outage, cancel emergency
96 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}.
97
98power_off(get_iac_pid, From, LoopDat) ->
99 Iac = LoopDat#lsc_state.iac_pid,
100 {reply, {ok, Iac}, power_off, LoopDat}.
101
102
103%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
104% STATE: out_of_service
105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
106
107out_of_service(start, LoopDat) ->
108 % Start from L3
109 send_to(rc, start, LoopDat),
110 send_to(txc, start, LoopDat),
111 case LoopDat#lsc_state.emergency of
112 1 ->
113 send_to(iac, emergency, LoopDat);
114 _ ->
115 ok
116 end,
117 send_to(iac, start, LoopDat),
118 {next_state, initial_alignment, LoopDat};
119
120out_of_service(retrieve_bsnt, LoopDat) ->
121 send_to(rc, retrieve_bsnt, LoopDat),
122 {next_state, out_of_service, LoopDat};
123
124out_of_service(retrieval_request_and_fsnc, LoopDat) ->
125 send_to(txc, retrieval_request_and_fsnc, LoopDat),
126 {next_state, out_of_service, LoopDat};
127
128out_of_service(emergency, LoopDat) ->
129 {next_state, out_of_service, LoopDat#lsc_state{emergency=1}};
130
131out_of_service(emergency_ceases, LoopDat) ->
132 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
133
134out_of_service(What, LoopDat) when What == local_processor_outage;
135 What == level3_failure ->
136 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=1}};
137
Harald Weltee5014372012-01-19 23:19:34 +0100138out_of_service(si_os, LoopDat) ->
139 % this transition is not specified in Q.703, but it makes
140 % quite a bit of sense. yate M2PA requires it, too.
141 {next_state, out_of_service, LoopDat};
142
Harald Welteb6689882012-01-16 16:00:45 +0100143out_of_service(local_processor_recovered, LoopDat) ->
144 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0}}.
145
146
147%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
148% STATE: initial_alignment
149%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
150
151initial_alignment(What, LoopDat) when What == local_processor_outage;
152 What == level3_failure ->
153 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=1}};
154
155initial_alignment(local_processor_recovered, LoopDat) ->
156 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=0}};
157
158initial_alignment(emergency, LoopDat) ->
159 send_to(iac, emergency, LoopDat),
160 {next_state, initial_alignment, LoopDat#lsc_state{emergency=1}};
161
162initial_alignment(alignment_complete, LoopDat) ->
163 send_to(suerm, start, LoopDat),
164 {ok, T1} = timer:apply_after(LoopDat#lsc_state.t1_timeout,
165 gen_fsm, send_event,
166 [self(), {timer_expired, t1}]),
167 case LoopDat#lsc_state.local_proc_out of
168 1 ->
169 send_to(poc, local_processor_outage, LoopDat),
170 send_to(txc, si_po, LoopDat),
171 send_to(rc, reject_msu_fiso, LoopDat),
172 NextState = aligned_not_ready;
173 _ ->
174 send_to(txc, fisu, LoopDat),
175 send_to(rc, accept_msu_fiso, LoopDat),
176 NextState = aligned_ready
177 end,
178 {next_state, NextState, LoopDat#lsc_state{t1=T1}};
179
180initial_alignment(stop, LoopDat) ->
181 send_to(iac, stop, LoopDat),
182 send_to(rc, stop, LoopDat),
183 send_to(txc, si_os, LoopDat),
184 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
185
186initial_alignment(link_failure, LoopDat) ->
187 send_to(l3, out_of_service, LoopDat),
188 send_to(iac, stop, LoopDat),
189 send_to(rc, stop, LoopDat),
190 send_to(txc, si_os, LoopDat),
191 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
192
193initial_alignment(alignment_not_possible, LoopDat) ->
194 send_to(rc, stop, LoopDat),
195 send_to(txc, si_os, LoopDat),
196 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
197
Harald Welte70984972012-01-19 22:50:39 +0100198% forward into IAC sub-state-machine
Harald Welteb6689882012-01-16 16:00:45 +0100199initial_alignment(What, LoopDat) when
Harald Welte70984972012-01-19 22:50:39 +0100200 What == si_n; What == si_e; What == si_o; What == si_os;
201 What == fisu_msu_received ->
202 Iac = LoopDat#lsc_state.iac_pid,
203 gen_fsm:send_event(Iac, What),
Harald Welteb6689882012-01-16 16:00:45 +0100204 {next_state, initial_alignment, LoopDat}.
205
206
207%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
208% STATE: aligned_ready
209%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
210
211aligned_ready(SioOrSios, LoopDat) when SioOrSios == si_o;
212 SioOrSios == si_os;
213 SioOrSios == link_failure ->
214 timer:cancel(LoopDat#lsc_state.t1),
215 send_to(l3, out_of_service, LoopDat),
216 send_to(rc, stop, LoopDat),
217 send_to(suerm, stop, LoopDat),
218 send_to(txc, si_os, LoopDat),
219 {next_state, out_of_service, LoopDat};
220
221aligned_ready(stop, LoopDat) ->
222 timer:cancel(LoopDat#lsc_state.t1),
223 send_to(rc, stop, LoopDat),
224 send_to(suerm, stop, LoopDat),
225 send_to(txc, si_os, LoopDat),
226 {next_state, out_of_service, LoopDat};
227
228aligned_ready({timer_expired, t1}, LoopDat) ->
229 send_to(l3, out_of_service, LoopDat),
230 send_to(rc, stop, LoopDat),
231 send_to(suerm, stop, LoopDat),
232 send_to(txc, si_os, LoopDat),
233 {next_state, out_of_service, LoopDat};
234
235aligned_ready(si_po, LoopDat) ->
236 timer:cancel(LoopDat#lsc_state.t1),
237 send_to(l3, remote_processor_outage, LoopDat),
238 send_to(poc, remote_processor_outage, LoopDat),
239 {next_state, processor_outage, LoopDat};
240
241aligned_ready(fisu_msu_received, LoopDat) ->
242 send_to(l3, in_service, LoopDat),
243 timer:cancel(LoopDat#lsc_state.t1),
244 send_to(txc, msu, LoopDat),
245 {next_state, in_service, LoopDat};
246aligned_ready(What, LoopDat) when What == local_processor_outage;
247 What == level3_failure ->
248 send_to(poc, local_processor_outage, LoopDat),
249 send_to(txc, si_po, LoopDat),
250 send_to(rc, reject_msu_fiso, LoopDat),
251 {next_state, aligned_not_ready, LoopDat}.
252
253
254%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
255% STATE: aligned_not_ready
256%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
257
258aligned_not_ready(Err, LoopDat) when Err == link_failure;
259 Err == si_o;
260 Err == si_os ->
261 timer:cancel(LoopDat#lsc_state.t1),
262 send_to(l3, out_of_service, LoopDat),
263 send_to(l3, stop, LoopDat),
264 send_to(suerm, stop, LoopDat),
265 send_to(txc, si_os, LoopDat),
266 send_to(poc, stop, LoopDat),
267 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
268
269aligned_not_ready(stop, LoopDat) ->
270 timer:cancel(LoopDat#lsc_state.t1),
271 send_to(l3, stop, LoopDat),
272 send_to(suerm, stop, LoopDat),
273 send_to(txc, si_os, LoopDat),
274 send_to(poc, stop, LoopDat),
275 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
276
277aligned_not_ready({timer_expired, t1}, LoopDat) ->
278 send_to(l3, stop, LoopDat),
279 send_to(suerm, stop, LoopDat),
280 send_to(txc, si_os, LoopDat),
281 send_to(poc, stop, LoopDat),
282 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
283
284aligned_not_ready(local_processor_recovered, LoopDat) ->
285 send_to(poc, local_processor_recovered, LoopDat),
286 send_to(txc, fisu, LoopDat),
287 send_to(rc, accept_msu_fisu, LoopDat),
288 {next_state, aligned_ready, LoopDat#lsc_state{local_proc_out=0}};
289
290aligned_not_ready(fisu_msu_received, LoopDat) ->
291 send_to(l3, in_service, LoopDat),
292 timer:cancel(LoopDat#lsc_state.t1),
293 {next_state, processor_outage, LoopDat};
294
295aligned_not_ready(si_po, LoopDat) ->
296 send_to(l3, remote_processor_outage, LoopDat),
297 send_to(poc, remote_processor_outage, LoopDat),
298 timer:cancel(LoopDat#lsc_state.t1),
299 {next_state, processor_outage, LoopDat}.
300
301
302%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
303% STATE: in_service
304%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
305
306in_service(What, LoopDat) when What == link_failure;
307 What == si_o;
308 What == si_n;
309 What == si_e;
310 What == si_os ->
311 send_to(l3, out_of_service, LoopDat),
312 send_to(suerm, stop, LoopDat),
313 send_to(rc, stop, LoopDat),
314 send_to(txc, si_os, LoopDat),
315 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
316
317in_service(stop, LoopDat) ->
318 send_to(suerm, stop, LoopDat),
319 send_to(rc, stop, LoopDat),
320 send_to(txc, si_os, LoopDat),
321 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
322
323in_service(What, LoopDat) when What == local_processor_outage;
324 What == level3_failure ->
325 send_to(poc, local_processor_outage, LoopDat),
326 send_to(txc, si_po, LoopDat),
327 send_to(rc, reject_msu_fisu, LoopDat),
328 {next_state, aligned_not_ready, LoopDat#lsc_state{local_proc_out=1}};
329
330in_service(si_po, LoopDat) ->
331 send_to(txc, fisu, LoopDat),
332 send_to(l3, remote_processor_outage, LoopDat),
333 send_to(poc, remote_processor_outage, LoopDat),
334 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}.
335
336
337%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
338% STATE: processor_outage
339%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
340
341processor_outage(retrieval_request_and_fsnc, LoopDat) ->
342 send_to(txc, retrieval_request_and_fsnc, LoopDat),
343 {next_state, processor_outage, LoopDat};
344
345processor_outage(fisu_msu_received, LoopDat) ->
346 send_to(poc, remote_processor_recovered, LoopDat),
347 send_to(l3, remote_processor_recovered, LoopDat),
348 {next_state, processor_outage, LoopDat};
349
350processor_outage(retrieve_bsnt, LoopDat) ->
351 send_to(rc, retrieve_bsnt, LoopDat),
352 {next_state, processor_outage, LoopDat};
353
354processor_outage(What, LoopDat) when What == local_processor_outage;
355 What == level3_failure ->
356 send_to(poc, local_processor_outage, LoopDat),
357 send_to(txc, si_po, LoopDat),
358 {next_state, processor_outage, LoopDat#lsc_state{local_proc_out=1}};
359
360processor_outage(si_po, LoopDat) ->
361 send_to(l3, remote_processor_outage, LoopDat),
362 send_to(poc, remote_processor_outage, LoopDat),
363 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}};
364
365processor_outage(local_processor_recovered, LoopDat) ->
366 send_to(poc, local_processor_recovered, LoopDat),
367 send_to(rc, retrieve_fsnx, LoopDat),
368 send_to(txc, fisu, LoopDat),
369 {next_state, processor_outage, LoopDat};
370
371processor_outage(flush_buffers, LoopDat) ->
372 send_to(txc, flush_buffers, LoopDat),
373 % FIXME: mark L3 ind recv
374 {next_state, processor_outage, LoopDat};
375
376processor_outage(no_processor_outage, LoopDat) ->
377 % FIXME: check L3 ind
378 send_to(txc, msu, LoopDat),
379 send_to(rc, accept_msu_fisu, LoopDat),
380 {next_state, in_service, LoopDat#lsc_state{local_proc_out=0, proc_out=0}};
381
382processor_outage(What, LoopDat) when What == link_failure;
383 What == si_o;
384 What == si_n;
385 What == si_e;
386 What == si_os ->
387 send_to(l3, out_of_service, LoopDat),
388 send_to(suerm, stop, LoopDat),
389 send_to(rc, stop, LoopDat),
390 send_to(poc, stop, LoopDat),
391 send_to(txc, si_os, LoopDat),
392 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}};
393
394processor_outage(stop, LoopDat) ->
395 send_to(suerm, stop, LoopDat),
396 send_to(rc, stop, LoopDat),
397 send_to(poc, stop, LoopDat),
398 send_to(txc, si_os, LoopDat),
399 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}.
400
401
402
403%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
404% helper functions
405%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
406send_to(txc, What, #lsc_state{txc_pid = Txc}) ->
407 Txc ! {lsc_txc, What};
408send_to(iac, What, #lsc_state{iac_pid = Iac}) ->
409 gen_fsm:send_event(Iac, What);
410send_to(Who, What, _LoopDat) ->
411 io:format("Not sending LSC -> ~p: ~p~n", [Who, What]).
412