blob: 2d19c1cdecbd7db33b5a19d484203af61b9fe3a7 [file] [log] [blame]
Harald Weltefa8ada02012-01-16 15:59:45 +01001% MTP3 Signalling Link Test Control (SLTC) according to Q.707
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 Weltefa8ada02012-01-16 15:59:45 +010033
34-module(mtp3_sltc).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(gen_fsm).
37
38-include("mtp3.hrl").
39
40% gen_fsm exports
41-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
42
43% individual FSM states
44-export([idle/2, first_attempt/2, second_attempt/2]).
45
46-record(sltc_state, {
47 hmrt_pid,
48 mgmt_pid,
49 lsac_pid,
50 sls,
51 opc,
52 adj_dpc,
53 t1,
54 t1_timeout,
55 x
56 }).
57
58-define(SLTC_T1_DEF, 10000).
59-define(SLTC_T2_DEF, 60000).
60
61%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
62% gen_fsm callbacks
63%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
64
65init([Hmrt, Mgmt, Lsac, Sls, AdjDpc, Opc]) when
66 is_pid(Hmrt), is_pid(Mgmt), is_pid(Lsac), is_integer(Sls) ->
67 SltState = #sltc_state{hmrt_pid = Hmrt,
68 mgmt_pid = Mgmt,
69 lsac_pid = Lsac,
70 sls = Sls,
71 adj_dpc = AdjDpc,
72 opc = Opc,
73 t1_timeout = ?SLTC_T1_DEF,
74 x = 16#2342},
75 {ok, idle, SltState}.
76
77terminate(Reason, State, _LoopDat) ->
78 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
79 [?MODULE, State, Reason]),
80 ok.
81
82code_change(_OldVsn, StateName, LoopDat, _Extra) ->
83 {ok, StateName, LoopDat}.
84
85handle_event(Event, State, LoopDat) ->
86 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
87 {next_state, State, LoopDat}.
88
89handle_info(Info, State, LoopDat) ->
90 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
91 {next_state, State, LoopDat}.
92
93% See Figure 2 of Q.707
94
95%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
96% STATE: idle
97%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
98
Harald Welte26bdef22012-01-16 22:22:17 +010099idle(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100100 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
101 h1 = ?MTP3MG_H1_SLTM}}, LoopDat) ->
102 Slta = slta_from_sltm(M),
103 send_to(hmrt, Slta, LoopDat),
104 {next_state, idle, LoopDat};
105
106idle(start, LoopDat) ->
107 Sltm = generate_sltm(LoopDat),
108 send_to(hmrt, Sltm, LoopDat),
109 {ok, T1} = timer:apply_after(gen_fsm, send_event,
110 [self(), {timer_expired, t1}]),
111 {next_state, first_attempt, LoopDat#sltc_state{t1 = T1}}.
112
113
114%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
115% STATE: first_attempt
116%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
117
Harald Welte26bdef22012-01-16 22:22:17 +0100118first_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100119 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
120 h1 = ?MTP3MG_H1_SLTM}}, LoopDat) ->
121 Slta = slta_from_sltm(M),
122 send_to(hmrt, Slta, LoopDat),
123 {next_state, first_attempt, LoopDat};
124
Harald Welte26bdef22012-01-16 22:22:17 +0100125first_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100126 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
127 h1 = ?MTP3MG_H1_SLTA}}, LoopDat) ->
128 timer:cancel(LoopDat#sltc_state.t1),
129 case slt_matches(M, LoopDat) of
130 true ->
131 send_to(lsac, slt_successful, LoopDat),
132 {next_state, idle, LoopDat};
133 false ->
134 Sltm = generate_sltm(LoopDat),
135 send_to(hmrt, Sltm, LoopDat),
136 {ok, T1} = timer:apply_after(gen_fsm, send_event,
137 [self(), {timer_expired, t1}]),
138 {next_state, second_attempt, LoopDat#sltc_state{t1 = T1}}
139 end.
140
141
142%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
143% STATE: second_attempt
144%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
145
Harald Welte26bdef22012-01-16 22:22:17 +0100146second_attempt(M=#mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100147 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
148 h1 = ?MTP3MG_H1_SLTM}}, LoopDat) ->
149 Slta = slta_from_sltm(M),
150 send_to(hmrt, Slta, LoopDat),
151 {next_state, second_attempt, LoopDat};
152
Harald Welte26bdef22012-01-16 22:22:17 +0100153second_attempt(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100154 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
155 h1 = ?MTP3MG_H1_SLTA}}, LoopDat) ->
156 timer:cancel(LoopDat#sltc_state.t1),
157 case slt_matches(M, LoopDat) of
158 true ->
159 send_to(lsac, slt_successful, LoopDat);
160 false ->
161 send_to(mgmt, slt_failed, LoopDat),
162 send_to(lsac, slt_failed, LoopDat)
163 end,
164 {next_state, idle, LoopDat};
165
166second_attempt({timer_expired, t1}, LoopDat) ->
167 send_to(mgmt, slt_failed, LoopDat),
168 send_to(lsac, slt_failed, LoopDat),
169 {next_state, idle, LoopDat}.
170
171
172%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
173% helper functions
174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
175send_to(hmrt, What, #sltc_state{hmrt_pid = Txc}) ->
176 Txc ! {sltc_hmrt, What};
177send_to(mgmt, What, #sltc_state{mgmt_pid = Txc}) ->
178 Txc ! {sltc_mgmt, What};
179send_to(lsac, What, #sltc_state{lsac_pid = Txc}) ->
180 Txc ! {sltc_lsac, What}.
181
Harald Welte26bdef22012-01-16 22:22:17 +0100182slta_from_sltm(M = #mtp3_msg{service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100183 routing_label = RoutLbl,
184 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
185 h1 = ?MTP3MG_H1_SLTM,
Harald Welte26bdef22012-01-16 22:22:17 +0100186 payload = TP}}) ->
Harald Welte1180b7c2012-01-25 01:28:56 +0100187 InvRoutLbl = mtp3_codec:invert_rout_lbl(RoutLbl),
Harald Weltefa8ada02012-01-16 15:59:45 +0100188 M#mtp3_msg{routing_label = InvRoutLbl,
189 payload = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST,
190 h1 = ?MTP3MG_H1_SLTA,
Harald Welte26bdef22012-01-16 22:22:17 +0100191 payload = TP}}.
Harald Weltefa8ada02012-01-16 15:59:45 +0100192
193generate_sltm(LoopDat) ->
194 Mg = #mtp3mg_msg{h0 = ?MTP3MG_H0_TEST, h1 = ?MTP3MG_H1_SLTM,
Harald Welte26bdef22012-01-16 22:22:17 +0100195 payload = LoopDat#sltc_state.x},
Harald Weltefa8ada02012-01-16 15:59:45 +0100196 Lbl = #mtp3_routing_label{sig_link_sel = LoopDat#sltc_state.sls,
197 origin_pc = LoopDat#sltc_state.opc,
198 dest_pc = LoopDat#sltc_state.adj_dpc},
199
200 #mtp3_msg{network_ind = ?MTP3_NETIND_INTERNATIONAL,
Harald Welte26bdef22012-01-16 22:22:17 +0100201 service_ind = ?MTP3_SERV_MTN,
Harald Weltefa8ada02012-01-16 15:59:45 +0100202 routing_label = Lbl, payload = Mg}.
203
204rout_lbl_matches(#mtp3_routing_label{sig_link_sel = SlsLocal,
205 origin_pc = OPC}, LoopDat) ->
206 #sltc_state{adj_dpc = AdjDpc, sls = SLS} = LoopDat,
207 if SLS == SlsLocal, OPC == AdjDpc ->
208 true;
209 true ->
210 false
211 end.
212
213slt_matches(#mtp3_msg{routing_label = RoutLbl,
Harald Welte26bdef22012-01-16 22:22:17 +0100214 payload = #mtp3mg_msg{payload = TP}}, LoopDat) ->
Harald Weltefa8ada02012-01-16 15:59:45 +0100215 case LoopDat#sltc_state.x of
216 TP ->
217 rout_lbl_matches(RoutLbl, LoopDat);
218 _ ->
219 false
220 end.