blob: 9bcce0d424cb303cfd4c532a17ba5917125e3591 [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
138out_of_service(local_processor_recovered, LoopDat) ->
139 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0}}.
140
141
142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
143% STATE: initial_alignment
144%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
145
146initial_alignment(What, LoopDat) when What == local_processor_outage;
147 What == level3_failure ->
148 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=1}};
149
150initial_alignment(local_processor_recovered, LoopDat) ->
151 {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=0}};
152
153initial_alignment(emergency, LoopDat) ->
154 send_to(iac, emergency, LoopDat),
155 {next_state, initial_alignment, LoopDat#lsc_state{emergency=1}};
156
157initial_alignment(alignment_complete, LoopDat) ->
158 send_to(suerm, start, LoopDat),
159 {ok, T1} = timer:apply_after(LoopDat#lsc_state.t1_timeout,
160 gen_fsm, send_event,
161 [self(), {timer_expired, t1}]),
162 case LoopDat#lsc_state.local_proc_out of
163 1 ->
164 send_to(poc, local_processor_outage, LoopDat),
165 send_to(txc, si_po, LoopDat),
166 send_to(rc, reject_msu_fiso, LoopDat),
167 NextState = aligned_not_ready;
168 _ ->
169 send_to(txc, fisu, LoopDat),
170 send_to(rc, accept_msu_fiso, LoopDat),
171 NextState = aligned_ready
172 end,
173 {next_state, NextState, LoopDat#lsc_state{t1=T1}};
174
175initial_alignment(stop, LoopDat) ->
176 send_to(iac, stop, LoopDat),
177 send_to(rc, stop, LoopDat),
178 send_to(txc, si_os, LoopDat),
179 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
180
181initial_alignment(link_failure, LoopDat) ->
182 send_to(l3, out_of_service, LoopDat),
183 send_to(iac, stop, LoopDat),
184 send_to(rc, stop, LoopDat),
185 send_to(txc, si_os, LoopDat),
186 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
187
188initial_alignment(alignment_not_possible, 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
Harald Welte70984972012-01-19 22:50:39 +0100193% forward into IAC sub-state-machine
Harald Welteb6689882012-01-16 16:00:45 +0100194initial_alignment(What, LoopDat) when
Harald Welte70984972012-01-19 22:50:39 +0100195 What == si_n; What == si_e; What == si_o; What == si_os;
196 What == fisu_msu_received ->
197 Iac = LoopDat#lsc_state.iac_pid,
198 gen_fsm:send_event(Iac, What),
Harald Welteb6689882012-01-16 16:00:45 +0100199 {next_state, initial_alignment, LoopDat}.
200
201
202%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
203% STATE: aligned_ready
204%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
205
206aligned_ready(SioOrSios, LoopDat) when SioOrSios == si_o;
207 SioOrSios == si_os;
208 SioOrSios == link_failure ->
209 timer:cancel(LoopDat#lsc_state.t1),
210 send_to(l3, out_of_service, LoopDat),
211 send_to(rc, stop, LoopDat),
212 send_to(suerm, stop, LoopDat),
213 send_to(txc, si_os, LoopDat),
214 {next_state, out_of_service, LoopDat};
215
216aligned_ready(stop, LoopDat) ->
217 timer:cancel(LoopDat#lsc_state.t1),
218 send_to(rc, stop, LoopDat),
219 send_to(suerm, stop, LoopDat),
220 send_to(txc, si_os, LoopDat),
221 {next_state, out_of_service, LoopDat};
222
223aligned_ready({timer_expired, t1}, LoopDat) ->
224 send_to(l3, out_of_service, LoopDat),
225 send_to(rc, stop, LoopDat),
226 send_to(suerm, stop, LoopDat),
227 send_to(txc, si_os, LoopDat),
228 {next_state, out_of_service, LoopDat};
229
230aligned_ready(si_po, LoopDat) ->
231 timer:cancel(LoopDat#lsc_state.t1),
232 send_to(l3, remote_processor_outage, LoopDat),
233 send_to(poc, remote_processor_outage, LoopDat),
234 {next_state, processor_outage, LoopDat};
235
236aligned_ready(fisu_msu_received, LoopDat) ->
237 send_to(l3, in_service, LoopDat),
238 timer:cancel(LoopDat#lsc_state.t1),
239 send_to(txc, msu, LoopDat),
240 {next_state, in_service, LoopDat};
241aligned_ready(What, LoopDat) when What == local_processor_outage;
242 What == level3_failure ->
243 send_to(poc, local_processor_outage, LoopDat),
244 send_to(txc, si_po, LoopDat),
245 send_to(rc, reject_msu_fiso, LoopDat),
246 {next_state, aligned_not_ready, LoopDat}.
247
248
249%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
250% STATE: aligned_not_ready
251%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
252
253aligned_not_ready(Err, LoopDat) when Err == link_failure;
254 Err == si_o;
255 Err == si_os ->
256 timer:cancel(LoopDat#lsc_state.t1),
257 send_to(l3, out_of_service, LoopDat),
258 send_to(l3, stop, LoopDat),
259 send_to(suerm, stop, LoopDat),
260 send_to(txc, si_os, LoopDat),
261 send_to(poc, stop, LoopDat),
262 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
263
264aligned_not_ready(stop, LoopDat) ->
265 timer:cancel(LoopDat#lsc_state.t1),
266 send_to(l3, stop, LoopDat),
267 send_to(suerm, stop, LoopDat),
268 send_to(txc, si_os, LoopDat),
269 send_to(poc, stop, LoopDat),
270 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
271
272aligned_not_ready({timer_expired, t1}, LoopDat) ->
273 send_to(l3, stop, LoopDat),
274 send_to(suerm, stop, LoopDat),
275 send_to(txc, si_os, LoopDat),
276 send_to(poc, stop, LoopDat),
277 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
278
279aligned_not_ready(local_processor_recovered, LoopDat) ->
280 send_to(poc, local_processor_recovered, LoopDat),
281 send_to(txc, fisu, LoopDat),
282 send_to(rc, accept_msu_fisu, LoopDat),
283 {next_state, aligned_ready, LoopDat#lsc_state{local_proc_out=0}};
284
285aligned_not_ready(fisu_msu_received, LoopDat) ->
286 send_to(l3, in_service, LoopDat),
287 timer:cancel(LoopDat#lsc_state.t1),
288 {next_state, processor_outage, LoopDat};
289
290aligned_not_ready(si_po, LoopDat) ->
291 send_to(l3, remote_processor_outage, LoopDat),
292 send_to(poc, remote_processor_outage, LoopDat),
293 timer:cancel(LoopDat#lsc_state.t1),
294 {next_state, processor_outage, LoopDat}.
295
296
297%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
298% STATE: in_service
299%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
300
301in_service(What, LoopDat) when What == link_failure;
302 What == si_o;
303 What == si_n;
304 What == si_e;
305 What == si_os ->
306 send_to(l3, out_of_service, LoopDat),
307 send_to(suerm, stop, LoopDat),
308 send_to(rc, stop, LoopDat),
309 send_to(txc, si_os, LoopDat),
310 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
311
312in_service(stop, LoopDat) ->
313 send_to(suerm, stop, LoopDat),
314 send_to(rc, stop, LoopDat),
315 send_to(txc, si_os, LoopDat),
316 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
317
318in_service(What, LoopDat) when What == local_processor_outage;
319 What == level3_failure ->
320 send_to(poc, local_processor_outage, LoopDat),
321 send_to(txc, si_po, LoopDat),
322 send_to(rc, reject_msu_fisu, LoopDat),
323 {next_state, aligned_not_ready, LoopDat#lsc_state{local_proc_out=1}};
324
325in_service(si_po, LoopDat) ->
326 send_to(txc, fisu, LoopDat),
327 send_to(l3, remote_processor_outage, LoopDat),
328 send_to(poc, remote_processor_outage, LoopDat),
329 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}.
330
331
332%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
333% STATE: processor_outage
334%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
335
336processor_outage(retrieval_request_and_fsnc, LoopDat) ->
337 send_to(txc, retrieval_request_and_fsnc, LoopDat),
338 {next_state, processor_outage, LoopDat};
339
340processor_outage(fisu_msu_received, LoopDat) ->
341 send_to(poc, remote_processor_recovered, LoopDat),
342 send_to(l3, remote_processor_recovered, LoopDat),
343 {next_state, processor_outage, LoopDat};
344
345processor_outage(retrieve_bsnt, LoopDat) ->
346 send_to(rc, retrieve_bsnt, LoopDat),
347 {next_state, processor_outage, LoopDat};
348
349processor_outage(What, LoopDat) when What == local_processor_outage;
350 What == level3_failure ->
351 send_to(poc, local_processor_outage, LoopDat),
352 send_to(txc, si_po, LoopDat),
353 {next_state, processor_outage, LoopDat#lsc_state{local_proc_out=1}};
354
355processor_outage(si_po, LoopDat) ->
356 send_to(l3, remote_processor_outage, LoopDat),
357 send_to(poc, remote_processor_outage, LoopDat),
358 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}};
359
360processor_outage(local_processor_recovered, LoopDat) ->
361 send_to(poc, local_processor_recovered, LoopDat),
362 send_to(rc, retrieve_fsnx, LoopDat),
363 send_to(txc, fisu, LoopDat),
364 {next_state, processor_outage, LoopDat};
365
366processor_outage(flush_buffers, LoopDat) ->
367 send_to(txc, flush_buffers, LoopDat),
368 % FIXME: mark L3 ind recv
369 {next_state, processor_outage, LoopDat};
370
371processor_outage(no_processor_outage, LoopDat) ->
372 % FIXME: check L3 ind
373 send_to(txc, msu, LoopDat),
374 send_to(rc, accept_msu_fisu, LoopDat),
375 {next_state, in_service, LoopDat#lsc_state{local_proc_out=0, proc_out=0}};
376
377processor_outage(What, LoopDat) when What == link_failure;
378 What == si_o;
379 What == si_n;
380 What == si_e;
381 What == si_os ->
382 send_to(l3, out_of_service, LoopDat),
383 send_to(suerm, stop, LoopDat),
384 send_to(rc, stop, LoopDat),
385 send_to(poc, stop, LoopDat),
386 send_to(txc, si_os, LoopDat),
387 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}};
388
389processor_outage(stop, LoopDat) ->
390 send_to(suerm, stop, LoopDat),
391 send_to(rc, stop, LoopDat),
392 send_to(poc, stop, LoopDat),
393 send_to(txc, si_os, LoopDat),
394 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}.
395
396
397
398%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
399% helper functions
400%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
401send_to(txc, What, #lsc_state{txc_pid = Txc}) ->
402 Txc ! {lsc_txc, What};
403send_to(iac, What, #lsc_state{iac_pid = Iac}) ->
404 gen_fsm:send_event(Iac, What);
405send_to(Who, What, _LoopDat) ->
406 io:format("Not sending LSC -> ~p: ~p~n", [Who, What]).
407