blob: 3965eb3e81160d8b2f702ee53f8d3ff5320af63a [file] [log] [blame]
Harald Welteb6689882012-01-16 16:00:45 +01001% MTP2 Initial Alignment Control according to Q.703 Figure 4 / Figure 9
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_iac).
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% states in this FSM
42-export([idle/2, not_aligned/2, aligned/2, proving/2]).
43
44% Timeouts in milliseconds According to Q.703 / Section 12.3
45-define(M2PA_T1_DEF, 50000).
46-define(M2PA_T2_DEF, 150000).
47-define(M2PA_T3_DEF, 2000).
48-define(M2PA_T4N_DEF, 8200).
49-define(M2PA_T4E_DEF, 500).
50
51-record(iac_state, {
52 t2_timeout,
53 t3_timeout,
54 t4_timeout,
55 t4_timeout_pn,
56 t4_timeout_pe,
57 t2, t3, t4,
58 emergency,
59 cp,
60 further_prov,
61 lsc_pid,
62 aerm_pid,
63 txc_pid
64 }).
65
66%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
67% gen_fsm callbacks
68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69
70init([Lsc, Aerm, Txc]) ->
71 IacState = #iac_state{t2_timeout = ?M2PA_T2_DEF,
72 t3_timeout = ?M2PA_T3_DEF,
73 t4_timeout_pn = ?M2PA_T4N_DEF,
74 t4_timeout_pe = ?M2PA_T4E_DEF,
75 emergency = 0,
76 cp = 0,
77 further_prov = 1,
78 lsc_pid = Lsc,
79 aerm_pid = Aerm,
80 txc_pid = Txc},
81 {ok, idle, IacState}.
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% STATE "idle"
102%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
103
104idle(start, LoopDat) ->
105 % send sio
106 send_to_txc(si_o, LoopDat),
107 % start timer
108 T2tout = LoopDat#iac_state.t2_timeout,
109 {ok, T2} = timer:apply_after(T2tout, gen_fsm, send_event,
110 [self(), {timer_expired, t2}]),
111 {next_state, not_aligned, LoopDat#iac_state{t2 = T2}};
112idle(emergency, LoopDat) ->
113 % mark emergency
114 {next_state, idle, LoopDat#iac_state{emergency = 1}}.
115
116
117%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
118% STATE "not aligned"
119%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
120
121not_aligned(stop, LoopDat) ->
122 % stop T2
123 timer:cancel(LoopDat#iac_state.t2),
124 % cancel emergency
125 {next_state, idle, LoopDat#iac_state{emergency=0}};
126not_aligned(si_e, LoopDat) ->
127 % stop T2
128 timer:cancel(LoopDat#iac_state.t2),
129 T4tout = LoopDat#iac_state.t4_timeout_pe,
130 % send SIE or SIN
131 case LoopDat#iac_state.emergency of
132 0 ->
133 Send = si_n;
134 _ ->
135 Send = si_e
136 end,
137 send_to_txc(Send, LoopDat),
138 % start T3
139 T3tout = LoopDat#iac_state.t3_timeout,
140 {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event,
141 [self(), {timer_expired, t3}]),
142 {next_state, aligned, LoopDat#iac_state{t3 = T3, t2 = undefined, t4_timeout = T4tout}};
143not_aligned(What, LoopDat) when What == si_o; What == si_n ->
144 % stop T2
145 timer:cancel(LoopDat#iac_state.t2),
146 % send SIE or SIN
147 case LoopDat#iac_state.emergency of
148 0 ->
149 T4tout = LoopDat#iac_state.t4_timeout_pn,
150 Send = si_n;
151 _ ->
152 T4tout = LoopDat#iac_state.t4_timeout_pe,
153 Send = si_e
154 end,
155 send_to_txc(Send, LoopDat),
156 T3tout = LoopDat#iac_state.t3_timeout,
157 {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event,
158 [self(), {timer_expired, t3}]),
159 {next_state, aligned, LoopDat#iac_state{t3 = T3, t2 = undefined, t4_timeout = T4tout}};
160not_aligned(emergency, LoopDat) ->
161 % mark emergency
162 {next_state, not_aligned, LoopDat#iac_state{emergency=1}};
Harald Welte4d08a712012-01-19 22:30:17 +0100163not_aligned(si_os, LoopDat) ->
164 % ignore SIOS in this state, as some implementations (notably
165 % yate) seem to send it in violation of the spec
166 {next_state, not_aligned, LoopDat};
Harald Welteb6689882012-01-16 16:00:45 +0100167not_aligned({timer_expired, t2}, LoopDat) ->
168 % send 'alignment not possible' to LSC
169 send_to_lsc(alignment_not_possible, LoopDat),
170 % stop emergency
171 {next_state, idle, LoopDat#iac_state{emergency=0}}.
172
173
174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
175% STATE "aligned"
176%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
177aligned(What, LoopDat) when What == si_n; What == si_e ->
178 case What of
179 si_e ->
180 % set T4 to Pe
181 T4tout = LoopDat#iac_state.t4_timeout_pe;
182 _ ->
183 T4tout = LoopDat#iac_state.t4_timeout_pn
184 end,
185 % stop T3
186 timer:cancel(LoopDat#iac_state.t3),
187 ToutPE = LoopDat#iac_state.t4_timeout_pe,
188 case T4tout of
189 ToutPE ->
190 % set i to ie IAC->AERM
191 send_to_aerm(set_i_to_ie, LoopDat);
192 _ ->
193 ok
194 end,
195 % send Start to AERM
196 send_to_aerm(start, LoopDat),
197 % start T4
Harald Welteb6689882012-01-16 16:00:45 +0100198 {ok, T4} = timer:apply_after(T4tout, gen_fsm, send_event,
199 [self(), {timer_expired, t4}]),
200 % Cp := 0
201 % cancel further proving?
202 LoopDat2 = LoopDat#iac_state{t4 = T4, t4_timeout = T4tout,
203 cp = 0, further_prov = 0},
204 {next_state, proving, LoopDat2};
205aligned(emergency, LoopDat) ->
206 % Send SIE
207 send_to_txc(si_e, LoopDat),
208 T4tout = LoopDat#iac_state.t4_timeout_pe,
209 {next_State, aligned, LoopDat#iac_state{t4_timeout = T4tout}};
210aligned(si_os, LoopDat) ->
211 % Send alignment not possible
212 send_to_lsc(alignment_not_possible, LoopDat),
213 % stop T3
214 timer:cancel(LoopDat#iac_state.t3),
215 {next_state, idle, LoopDat#iac_state{emergency=0, t3=undefined}};
216aligned(stop, LoopDat) ->
217 % Stop T3
218 timer:cancel(LoopDat#iac_state.t3),
219 % cancel Emergency
220 {next_state, idle, LoopDat#iac_state{emergency=0, t3=undefined}};
221aligned({timer_expired, t3}, LoopDat) ->
222 % Send alignment not possible
223 send_to_lsc(alignment_not_possible, LoopDat),
224 % cancel emergency
225 {next_state, idle, LoopDat#iac_state{emergency=0}}.
226
227
228%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
229% STATE "proving"
230%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
231fig9_4(LoopDat) ->
232 % send Stop to AERM
233 send_to_aerm(stop, LoopDat),
234 % cancel emergency
235 {next_state, idle, LoopDat#iac_state{emergency=0}}.
236
237fig9_5(LoopDat) ->
238 % send Start to AERM
239 send_to_aerm(start, LoopDat),
240 % cancel further proving
241 % start T4
242 T4tout = LoopDat#iac_state.t4_timeout,
243 {ok, T4} = timer:apply_after(T4tout, gen_fsm, send_event,
244 [self(), {timer_expired, t4}]),
245 {next_state, proving, LoopDat#iac_state{t4=T4, further_prov=0}}.
246
247prov_emerg_or_sie(LoopDat) ->
248 % stop T4
249 timer:cancel(LoopDat#iac_state.t4),
250 % Set T4 to Pe
251 T4tout = LoopDat#iac_state.t4_timeout_pe,
252 % Send stop to AERM
253 send_to_aerm(stop, LoopDat),
254 % Send 'set ti to tie' to AERM
255 send_to_aerm(set_ti_to_tie, LoopDat),
256 fig9_5(LoopDat#iac_state{t4_timeout=T4tout, t4=undefined}).
257
258
259proving(expires, LoopDat) ->
260 % alignment complete
261 {next_state, idle, LoopDat};
262proving(si_e, LoopDat) ->
263 ToutPE = LoopDat#iac_state.t4_timeout_pe,
264 case LoopDat#iac_state.t4_timeout of
265 ToutPE ->
266 {next_state, proving, LoopDat};
267 _ ->
268 prov_emerg_or_sie(LoopDat)
269 end;
270proving(emergency, LoopDat) ->
271 prov_emerg_or_sie(LoopDat);
272proving(stop, LoopDat) ->
273 % stop T4
274 timer:cancel(LoopDat#iac_state.t4),
275 fig9_4(LoopDat);
276proving(si_os, LoopDat) ->
277 % stop T4
278 timer:cancel(LoopDat#iac_state.t4),
279 % Send alignment not possible to LSC
280 send_to_lsc(alignment_not_possible, LoopDat),
281 fig9_4(LoopDat);
282proving(high_err_rate, LoopDat) ->
283 % alignment not possible
284 {next_state, idle, LoopDat};
285proving(sio, LoopDat) ->
286 % stop T4
287 timer:cancel(LoopDat#iac_state.t4),
288 % send Stop to AERM
289 send_to_aerm(stop, LoopDat),
290 % start T3
291 T3tout = LoopDat#iac_state.t3_timeout,
292 {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event,
293 [self(), {timer_expired, t3}]),
294 {next_state, aligned, LoopDat#iac_state{t3=T3, t4=undefined}};
295proving(What, LoopDat) when What == correct_su; What == si_n ->
296 case LoopDat#iac_state.further_prov of
297 1 ->
298 % stop T4
299 timer:cancel(LoopDat#iac_state.t4),
300 fig9_5(LoopDat);
301 _ ->
302 {next_state, proving, LoopDat}
303 end;
304proving({timer_expired, t4}, LoopDat) ->
305 % check if we are further proving, if yes, call fig9_5
306 case LoopDat#iac_state.further_prov of
307 1 ->
308 fig9_5(LoopDat);
309 _ ->
310 % send 'aligment complete' to LSC
311 send_to_lsc(alignment_complete, LoopDat),
312 fig9_4(LoopDat)
313 end;
Harald Welteb6689882012-01-16 16:00:45 +0100314proving(abort_proving, LoopDat) ->
315 % Cp := Cp + 1
316 Cp = LoopDat#iac_state.cp,
317 LoopDat2 = LoopDat#iac_state{cp = Cp + 1},
318 case Cp + 1 of
319 5 ->
320 % send 'alignment not possible' to LSC
321 send_to_lsc(alignment_not_possible, LoopDat),
322 % stop T4
323 timer:cancel(LoopDat#iac_state.t4),
324 fig9_4(LoopDat2);
325 _ ->
326 % mark further proving
327 {next_state, proving, LoopDat2#iac_state{further_prov=1}}
328 end.
329
330
331%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
332% helper functions
333%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
334send_to_lsc(What, #iac_state{lsc_pid = Lsc}) ->
335 gen_fsm:send_event(Lsc, What).
336
337send_to_aerm(What, #iac_state{aerm_pid = Aerm}) ->
338 Aerm ! {iac_aerm, What}.
339
340send_to_txc(What, #iac_state{txc_pid = Txc}) ->
341 Txc ! {iac_txc, What}.