blob: 459d77b100c9d80ad5cddb391f1a06a3d3bc2fcc [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
193% ignore
194initial_alignment(What, LoopDat) when
195 What == si_n; What == si_e; What == si_o; What == si_os ->
196 {next_state, initial_alignment, LoopDat}.
197
198
199%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
200% STATE: aligned_ready
201%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
202
203aligned_ready(SioOrSios, LoopDat) when SioOrSios == si_o;
204 SioOrSios == si_os;
205 SioOrSios == link_failure ->
206 timer:cancel(LoopDat#lsc_state.t1),
207 send_to(l3, out_of_service, LoopDat),
208 send_to(rc, stop, LoopDat),
209 send_to(suerm, stop, LoopDat),
210 send_to(txc, si_os, LoopDat),
211 {next_state, out_of_service, LoopDat};
212
213aligned_ready(stop, LoopDat) ->
214 timer:cancel(LoopDat#lsc_state.t1),
215 send_to(rc, stop, LoopDat),
216 send_to(suerm, stop, LoopDat),
217 send_to(txc, si_os, LoopDat),
218 {next_state, out_of_service, LoopDat};
219
220aligned_ready({timer_expired, t1}, LoopDat) ->
221 send_to(l3, out_of_service, LoopDat),
222 send_to(rc, stop, LoopDat),
223 send_to(suerm, stop, LoopDat),
224 send_to(txc, si_os, LoopDat),
225 {next_state, out_of_service, LoopDat};
226
227aligned_ready(si_po, LoopDat) ->
228 timer:cancel(LoopDat#lsc_state.t1),
229 send_to(l3, remote_processor_outage, LoopDat),
230 send_to(poc, remote_processor_outage, LoopDat),
231 {next_state, processor_outage, LoopDat};
232
233aligned_ready(fisu_msu_received, LoopDat) ->
234 send_to(l3, in_service, LoopDat),
235 timer:cancel(LoopDat#lsc_state.t1),
236 send_to(txc, msu, LoopDat),
237 {next_state, in_service, LoopDat};
238aligned_ready(What, LoopDat) when What == local_processor_outage;
239 What == level3_failure ->
240 send_to(poc, local_processor_outage, LoopDat),
241 send_to(txc, si_po, LoopDat),
242 send_to(rc, reject_msu_fiso, LoopDat),
243 {next_state, aligned_not_ready, LoopDat}.
244
245
246%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
247% STATE: aligned_not_ready
248%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
249
250aligned_not_ready(Err, LoopDat) when Err == link_failure;
251 Err == si_o;
252 Err == si_os ->
253 timer:cancel(LoopDat#lsc_state.t1),
254 send_to(l3, out_of_service, LoopDat),
255 send_to(l3, stop, LoopDat),
256 send_to(suerm, stop, LoopDat),
257 send_to(txc, si_os, LoopDat),
258 send_to(poc, stop, LoopDat),
259 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
260
261aligned_not_ready(stop, LoopDat) ->
262 timer:cancel(LoopDat#lsc_state.t1),
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({timer_expired, t1}, LoopDat) ->
270 send_to(l3, stop, LoopDat),
271 send_to(suerm, stop, LoopDat),
272 send_to(txc, si_os, LoopDat),
273 send_to(poc, stop, LoopDat),
274 {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}};
275
276aligned_not_ready(local_processor_recovered, LoopDat) ->
277 send_to(poc, local_processor_recovered, LoopDat),
278 send_to(txc, fisu, LoopDat),
279 send_to(rc, accept_msu_fisu, LoopDat),
280 {next_state, aligned_ready, LoopDat#lsc_state{local_proc_out=0}};
281
282aligned_not_ready(fisu_msu_received, LoopDat) ->
283 send_to(l3, in_service, LoopDat),
284 timer:cancel(LoopDat#lsc_state.t1),
285 {next_state, processor_outage, LoopDat};
286
287aligned_not_ready(si_po, LoopDat) ->
288 send_to(l3, remote_processor_outage, LoopDat),
289 send_to(poc, remote_processor_outage, LoopDat),
290 timer:cancel(LoopDat#lsc_state.t1),
291 {next_state, processor_outage, LoopDat}.
292
293
294%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
295% STATE: in_service
296%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
297
298in_service(What, LoopDat) when What == link_failure;
299 What == si_o;
300 What == si_n;
301 What == si_e;
302 What == si_os ->
303 send_to(l3, out_of_service, LoopDat),
304 send_to(suerm, stop, LoopDat),
305 send_to(rc, stop, LoopDat),
306 send_to(txc, si_os, LoopDat),
307 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
308
309in_service(stop, LoopDat) ->
310 send_to(suerm, stop, LoopDat),
311 send_to(rc, stop, LoopDat),
312 send_to(txc, si_os, LoopDat),
313 {next_state, out_of_service, LoopDat#lsc_state{emergency=0}};
314
315in_service(What, LoopDat) when What == local_processor_outage;
316 What == level3_failure ->
317 send_to(poc, local_processor_outage, LoopDat),
318 send_to(txc, si_po, LoopDat),
319 send_to(rc, reject_msu_fisu, LoopDat),
320 {next_state, aligned_not_ready, LoopDat#lsc_state{local_proc_out=1}};
321
322in_service(si_po, LoopDat) ->
323 send_to(txc, fisu, LoopDat),
324 send_to(l3, remote_processor_outage, LoopDat),
325 send_to(poc, remote_processor_outage, LoopDat),
326 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}.
327
328
329%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
330% STATE: processor_outage
331%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
332
333processor_outage(retrieval_request_and_fsnc, LoopDat) ->
334 send_to(txc, retrieval_request_and_fsnc, LoopDat),
335 {next_state, processor_outage, LoopDat};
336
337processor_outage(fisu_msu_received, LoopDat) ->
338 send_to(poc, remote_processor_recovered, LoopDat),
339 send_to(l3, remote_processor_recovered, LoopDat),
340 {next_state, processor_outage, LoopDat};
341
342processor_outage(retrieve_bsnt, LoopDat) ->
343 send_to(rc, retrieve_bsnt, LoopDat),
344 {next_state, processor_outage, LoopDat};
345
346processor_outage(What, LoopDat) when What == local_processor_outage;
347 What == level3_failure ->
348 send_to(poc, local_processor_outage, LoopDat),
349 send_to(txc, si_po, LoopDat),
350 {next_state, processor_outage, LoopDat#lsc_state{local_proc_out=1}};
351
352processor_outage(si_po, LoopDat) ->
353 send_to(l3, remote_processor_outage, LoopDat),
354 send_to(poc, remote_processor_outage, LoopDat),
355 {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}};
356
357processor_outage(local_processor_recovered, LoopDat) ->
358 send_to(poc, local_processor_recovered, LoopDat),
359 send_to(rc, retrieve_fsnx, LoopDat),
360 send_to(txc, fisu, LoopDat),
361 {next_state, processor_outage, LoopDat};
362
363processor_outage(flush_buffers, LoopDat) ->
364 send_to(txc, flush_buffers, LoopDat),
365 % FIXME: mark L3 ind recv
366 {next_state, processor_outage, LoopDat};
367
368processor_outage(no_processor_outage, LoopDat) ->
369 % FIXME: check L3 ind
370 send_to(txc, msu, LoopDat),
371 send_to(rc, accept_msu_fisu, LoopDat),
372 {next_state, in_service, LoopDat#lsc_state{local_proc_out=0, proc_out=0}};
373
374processor_outage(What, LoopDat) when What == link_failure;
375 What == si_o;
376 What == si_n;
377 What == si_e;
378 What == si_os ->
379 send_to(l3, out_of_service, LoopDat),
380 send_to(suerm, stop, LoopDat),
381 send_to(rc, stop, LoopDat),
382 send_to(poc, stop, LoopDat),
383 send_to(txc, si_os, LoopDat),
384 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}};
385
386processor_outage(stop, LoopDat) ->
387 send_to(suerm, stop, LoopDat),
388 send_to(rc, stop, LoopDat),
389 send_to(poc, stop, LoopDat),
390 send_to(txc, si_os, LoopDat),
391 {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}.
392
393
394
395%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
396% helper functions
397%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
398send_to(txc, What, #lsc_state{txc_pid = Txc}) ->
399 Txc ! {lsc_txc, What};
400send_to(iac, What, #lsc_state{iac_pid = Iac}) ->
401 gen_fsm:send_event(Iac, What);
402send_to(Who, What, _LoopDat) ->
403 io:format("Not sending LSC -> ~p: ~p~n", [Who, What]).
404