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