diff options
author | Harald Welte <laforge@gnumonks.org> | 2012-01-16 16:00:45 +0100 |
---|---|---|
committer | Harald Welte <laforge@gnumonks.org> | 2012-01-16 16:00:45 +0100 |
commit | b668988e25d8edc98a73c4fde0f4a7a7133f5938 (patch) | |
tree | 4ceac8e323dfa92e6a6b345e24d1f4479f1d6787 | |
parent | fa8ada01454fca86f6ce8f278c60fcd392a6ede4 (diff) |
Add M2PA codec, MTP2 IAC and LSC gen_fsm implementations
-rw-r--r-- | include/m2pa.hrl | 51 | ||||
-rw-r--r-- | src/m2pa_codec.erl | 66 | ||||
-rw-r--r-- | src/mtp2_iac.erl | 324 | ||||
-rw-r--r-- | src/mtp2_lsc.erl | 404 |
4 files changed, 845 insertions, 0 deletions
diff --git a/include/m2pa.hrl b/include/m2pa.hrl new file mode 100644 index 0000000..959133d --- /dev/null +++ b/include/m2pa.hrl @@ -0,0 +1,51 @@ +% RFC 4165 MTP2 P2P Adaption Layer coding / decoding + +% (C) 2012 by Harald Welte <laforge@gnumonks.org> +% +% All Rights Reserved +% +% This program is free software; you can redistribute it and/or modify +% it under the terms of the GNU Affero General Public License as +% published by the Free Software Foundation; either version 3 of the +% License, or (at your option) any later version. +% +% This program is distributed in the hope that it will be useful, +% but WITHOUT ANY WARRANTY; without even the implied warranty of +% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +% GNU General Public License for more details. +% +% You should have received a copy of the GNU Affero General Public License +% along with this program. If not, see <http://www.gnu.org/licenses/>. + +-define(M2PA_PPID, 5). + +% Section 2.1.3 +-define(M2PA_CLASS_M2PA, 11). + +% Section 2.1.4 +-define(M2PA_TYPE_USER, 1). +-define(M2PA_TYPE_LINK, 2). + +% Section 2.3.2 +-define(M2PA_LS_ALIGNMENT, 1). +-define(M2PA_LS_PROVING_NORMAL, 2). +-define(M2PA_LS_PROVING_EMERG, 3). +-define(M2PA_LS_READY, 4). +-define(M2PA_LS_PROC_OUTAGE, 5). +-define(M2PA_LS_PROC_RECOVERED, 6). +-define(M2PA_LS_BUSY, 7). +-define(M2PA_LS_BUSY_ENDED, 8). +-define(M2PA_LS_OOS, 9). + +% SCTP stream IDs +-define(M2PA_STREAM_STATUS, 0). +-define(M2PA_STREAM_USER, 1). + +-record(m2pa_msg, { + msg_class, + msg_type, + fwd_seq_nr, + back_seq_nr, + mtp3, + parameters + }). diff --git a/src/m2pa_codec.erl b/src/m2pa_codec.erl new file mode 100644 index 0000000..585b9c9 --- /dev/null +++ b/src/m2pa_codec.erl @@ -0,0 +1,66 @@ +% RFC 4165 MTP2 P2P Adaption Layer coding / decoding + +% (C) 2012 by Harald Welte <laforge@gnumonks.org> +% +% All Rights Reserved +% +% This program is free software; you can redistribute it and/or modify +% it under the terms of the GNU Affero General Public License as +% published by the Free Software Foundation; either version 3 of the +% License, or (at your option) any later version. +% +% This program is distributed in the hope that it will be useful, +% but WITHOUT ANY WARRANTY; without even the implied warranty of +% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +% GNU General Public License for more details. +% +% You should have received a copy of the GNU Affero General Public License +% along with this program. If not, see <http://www.gnu.org/licenses/>. + +-module(m2pa_codec). +-author('Harald Welte <laforge@gnumonks.org>'). +-include("m2pa.hrl"). +-include("mtp3.hrl"). + +-export([parse_msg/1, encode_msg/1]). + +-compile({parse_transform, exprecs}). +-export_records([m2pa_msg]). + +parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, Len, Remain) -> + <<State:32/big, Filler/binary>> = Remain, + Ret = [{link_state, State}], + if + byte_size(Filler) > 0 -> + {undefined, [{filler, Filler}|Ret]}; + true -> + {undefined, Ret} + end; +parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Len, RemainIn) -> + <<Pri:1, _:7, SIO:8, SIF/binary>> = RemainIn, + Mtp3 = #mtp3_msg{service_ind = SIO, m3ua_mp = Pri, payload = SIF}, + {Mtp3, []}. + +parse_msg(DataBin) when is_binary(DataBin) -> + <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, AllRemain/binary>> = DataBin, + <<_:8, BSN:24/big, _:8, FSN:24/big, Remain/binary>> = AllRemain, + {Mtp3, Params} = parse_m2pa_msgt(MsgClass, MsgType, MsgLen, Remain), + {ok, #m2pa_msg{msg_class = MsgClass, msg_type = MsgType, + fwd_seq_nr = FSN, back_seq_nr = BSN, + mtp3 = Mtp3, parameters = Params}}. + +encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3, _Params) -> + <<Mtp3/binary>>; +encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, _, Params) -> + State = proplists:get_value(link_state, Params), + % FIXME: filler + Filler = <<>>, + <<State:32/big, Filler/binary>>. + + +encode_msg(Msg) when is_record(Msg, m2pa_msg) -> + #m2pa_msg{msg_class = MsgClass, msg_type = MsgType, fwd_seq_nr = FSN, + back_seq_nr = BSN, mtp3 = Mtp3, parameters = Params} = Msg, + Payload = encode_m2pa_msgt(MsgClass, MsgType, Mtp3, Params), + MsgLen = byte_size(Payload) + 16, + <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, 0:8, BSN:24/big, 0:8, FSN:24/big, Payload/binary>>. diff --git a/src/mtp2_iac.erl b/src/mtp2_iac.erl new file mode 100644 index 0000000..d23aaf0 --- /dev/null +++ b/src/mtp2_iac.erl @@ -0,0 +1,324 @@ +% MTP2 Initial Alignment Control according to Q.703 Figure 4 / Figure 9 + +% (C) 2011-2012 by Harald Welte <laforge@gnumonks.org> +% +% All Rights Reserved +% +% This program is free software; you can redistribute it and/or modify +% it under the terms of the GNU Affero General Public License as +% published by the Free Software Foundation; either version 3 of the +% License, or (at your option) any later version. +% +% This program is distributed in the hope that it will be useful, +% but WITHOUT ANY WARRANTY; without even the implied warranty of +% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +% GNU General Public License for more details. +% +% You should have received a copy of the GNU Affero General Public License +% along with this program. If not, see <http://www.gnu.org/licenses/>. + +-module(mtp2_iac). +-author('Harald Welte <laforge@gnumonks.org>'). +-behaviour(gen_fsm). + +% gen_fsm exports +-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]). + +% states in this FSM +-export([idle/2, not_aligned/2, aligned/2, proving/2]). + +% Timeouts in milliseconds According to Q.703 / Section 12.3 +-define(M2PA_T1_DEF, 50000). +-define(M2PA_T2_DEF, 150000). +-define(M2PA_T3_DEF, 2000). +-define(M2PA_T4N_DEF, 8200). +-define(M2PA_T4E_DEF, 500). + +-record(iac_state, { + t2_timeout, + t3_timeout, + t4_timeout, + t4_timeout_pn, + t4_timeout_pe, + t2, t3, t4, + emergency, + cp, + further_prov, + lsc_pid, + aerm_pid, + txc_pid + }). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% gen_fsm callbacks +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +init([Lsc, Aerm, Txc]) -> + IacState = #iac_state{t2_timeout = ?M2PA_T2_DEF, + t3_timeout = ?M2PA_T3_DEF, + t4_timeout_pn = ?M2PA_T4N_DEF, + t4_timeout_pe = ?M2PA_T4E_DEF, + emergency = 0, + cp = 0, + further_prov = 1, + lsc_pid = Lsc, + aerm_pid = Aerm, + txc_pid = Txc}, + {ok, idle, IacState}. + +terminate(Reason, State, _LoopDat) -> + io:format("Terminating ~p in State ~p (Reason: ~p)~n", + [?MODULE, State, Reason]), + ok. + +code_change(_OldVsn, StateName, LoopDat, _Extra) -> + {ok, StateName, LoopDat}. + +handle_event(Event, State, LoopDat) -> + io:format("Unknown Event ~p in state ~p~n", [Event, State]), + {next_state, State, LoopDat}. + + +handle_info(Info, State, LoopDat) -> + io:format("Unknown Info ~p in state ~p~n", [Info, State]), + {next_state, State, LoopDat}. + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE "idle" +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +idle(start, LoopDat) -> + % send sio + send_to_txc(si_o, LoopDat), + % start timer + T2tout = LoopDat#iac_state.t2_timeout, + {ok, T2} = timer:apply_after(T2tout, gen_fsm, send_event, + [self(), {timer_expired, t2}]), + {next_state, not_aligned, LoopDat#iac_state{t2 = T2}}; +idle(emergency, LoopDat) -> + % mark emergency + {next_state, idle, LoopDat#iac_state{emergency = 1}}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE "not aligned" +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +not_aligned(stop, LoopDat) -> + % stop T2 + timer:cancel(LoopDat#iac_state.t2), + % cancel emergency + {next_state, idle, LoopDat#iac_state{emergency=0}}; +not_aligned(si_e, LoopDat) -> + % stop T2 + timer:cancel(LoopDat#iac_state.t2), + T4tout = LoopDat#iac_state.t4_timeout_pe, + % send SIE or SIN + case LoopDat#iac_state.emergency of + 0 -> + Send = si_n; + _ -> + Send = si_e + end, + send_to_txc(Send, LoopDat), + % start T3 + T3tout = LoopDat#iac_state.t3_timeout, + {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event, + [self(), {timer_expired, t3}]), + {next_state, aligned, LoopDat#iac_state{t3 = T3, t2 = undefined, t4_timeout = T4tout}}; +not_aligned(What, LoopDat) when What == si_o; What == si_n -> + % stop T2 + timer:cancel(LoopDat#iac_state.t2), + % send SIE or SIN + case LoopDat#iac_state.emergency of + 0 -> + T4tout = LoopDat#iac_state.t4_timeout_pn, + Send = si_n; + _ -> + T4tout = LoopDat#iac_state.t4_timeout_pe, + Send = si_e + end, + send_to_txc(Send, LoopDat), + T3tout = LoopDat#iac_state.t3_timeout, + {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event, + [self(), {timer_expired, t3}]), + {next_state, aligned, LoopDat#iac_state{t3 = T3, t2 = undefined, t4_timeout = T4tout}}; +not_aligned(emergency, LoopDat) -> + % mark emergency + {next_state, not_aligned, LoopDat#iac_state{emergency=1}}; +not_aligned({timer_expired, t2}, LoopDat) -> + % send 'alignment not possible' to LSC + send_to_lsc(alignment_not_possible, LoopDat), + % stop emergency + {next_state, idle, LoopDat#iac_state{emergency=0}}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE "aligned" +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +aligned(What, LoopDat) when What == si_n; What == si_e -> + case What of + si_e -> + % set T4 to Pe + T4tout = LoopDat#iac_state.t4_timeout_pe; + _ -> + T4tout = LoopDat#iac_state.t4_timeout_pn + end, + % stop T3 + timer:cancel(LoopDat#iac_state.t3), + ToutPE = LoopDat#iac_state.t4_timeout_pe, + case T4tout of + ToutPE -> + % set i to ie IAC->AERM + send_to_aerm(set_i_to_ie, LoopDat); + _ -> + ok + end, + % send Start to AERM + send_to_aerm(start, LoopDat), + % start T4 + io:format("trying to start T4, T4tout=~p~n", [T4tout]), + {ok, T4} = timer:apply_after(T4tout, gen_fsm, send_event, + [self(), {timer_expired, t4}]), + % Cp := 0 + % cancel further proving? + LoopDat2 = LoopDat#iac_state{t4 = T4, t4_timeout = T4tout, + cp = 0, further_prov = 0}, + {next_state, proving, LoopDat2}; +aligned(emergency, LoopDat) -> + % Send SIE + send_to_txc(si_e, LoopDat), + T4tout = LoopDat#iac_state.t4_timeout_pe, + {next_State, aligned, LoopDat#iac_state{t4_timeout = T4tout}}; +aligned(si_os, LoopDat) -> + % Send alignment not possible + send_to_lsc(alignment_not_possible, LoopDat), + % stop T3 + timer:cancel(LoopDat#iac_state.t3), + {next_state, idle, LoopDat#iac_state{emergency=0, t3=undefined}}; +aligned(stop, LoopDat) -> + % Stop T3 + timer:cancel(LoopDat#iac_state.t3), + % cancel Emergency + {next_state, idle, LoopDat#iac_state{emergency=0, t3=undefined}}; +aligned({timer_expired, t3}, LoopDat) -> + % Send alignment not possible + send_to_lsc(alignment_not_possible, LoopDat), + % cancel emergency + {next_state, idle, LoopDat#iac_state{emergency=0}}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE "proving" +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +fig9_4(LoopDat) -> + % send Stop to AERM + send_to_aerm(stop, LoopDat), + % cancel emergency + {next_state, idle, LoopDat#iac_state{emergency=0}}. + +fig9_5(LoopDat) -> + % send Start to AERM + send_to_aerm(start, LoopDat), + % cancel further proving + % start T4 + T4tout = LoopDat#iac_state.t4_timeout, + {ok, T4} = timer:apply_after(T4tout, gen_fsm, send_event, + [self(), {timer_expired, t4}]), + {next_state, proving, LoopDat#iac_state{t4=T4, further_prov=0}}. + +prov_emerg_or_sie(LoopDat) -> + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + % Set T4 to Pe + T4tout = LoopDat#iac_state.t4_timeout_pe, + % Send stop to AERM + send_to_aerm(stop, LoopDat), + % Send 'set ti to tie' to AERM + send_to_aerm(set_ti_to_tie, LoopDat), + fig9_5(LoopDat#iac_state{t4_timeout=T4tout, t4=undefined}). + + +proving(expires, LoopDat) -> + % alignment complete + {next_state, idle, LoopDat}; +proving(si_e, LoopDat) -> + ToutPE = LoopDat#iac_state.t4_timeout_pe, + case LoopDat#iac_state.t4_timeout of + ToutPE -> + {next_state, proving, LoopDat}; + _ -> + prov_emerg_or_sie(LoopDat) + end; +proving(emergency, LoopDat) -> + prov_emerg_or_sie(LoopDat); +proving(stop, LoopDat) -> + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + fig9_4(LoopDat); +proving(si_os, LoopDat) -> + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + % Send alignment not possible to LSC + send_to_lsc(alignment_not_possible, LoopDat), + fig9_4(LoopDat); +proving(high_err_rate, LoopDat) -> + % alignment not possible + {next_state, idle, LoopDat}; +proving(sio, LoopDat) -> + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + % send Stop to AERM + send_to_aerm(stop, LoopDat), + % start T3 + T3tout = LoopDat#iac_state.t3_timeout, + {ok, T3} = timer:apply_after(T3tout, gen_fsm, send_event, + [self(), {timer_expired, t3}]), + {next_state, aligned, LoopDat#iac_state{t3=T3, t4=undefined}}; +proving(What, LoopDat) when What == correct_su; What == si_n -> + case LoopDat#iac_state.further_prov of + 1 -> + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + fig9_5(LoopDat); + _ -> + {next_state, proving, LoopDat} + end; +proving({timer_expired, t4}, LoopDat) -> + % check if we are further proving, if yes, call fig9_5 + case LoopDat#iac_state.further_prov of + 1 -> + fig9_5(LoopDat); + _ -> + % send 'aligment complete' to LSC + send_to_lsc(alignment_complete, LoopDat), + fig9_4(LoopDat) + end; +proving(abort_proving, LoopDat) -> + % Cp := Cp + 1 + Cp = LoopDat#iac_state.cp, + LoopDat2 = LoopDat#iac_state{cp = Cp + 1}, + case Cp + 1 of + 5 -> + % send 'alignment not possible' to LSC + send_to_lsc(alignment_not_possible, LoopDat), + % stop T4 + timer:cancel(LoopDat#iac_state.t4), + fig9_4(LoopDat2); + _ -> + % mark further proving + {next_state, proving, LoopDat2#iac_state{further_prov=1}} + end. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% helper functions +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +send_to_lsc(What, #iac_state{lsc_pid = Lsc}) -> + gen_fsm:send_event(Lsc, What). + +send_to_aerm(What, #iac_state{aerm_pid = Aerm}) -> + Aerm ! {iac_aerm, What}. + +send_to_txc(What, #iac_state{txc_pid = Txc}) -> + Txc ! {iac_txc, What}. diff --git a/src/mtp2_lsc.erl b/src/mtp2_lsc.erl new file mode 100644 index 0000000..459d77b --- /dev/null +++ b/src/mtp2_lsc.erl @@ -0,0 +1,404 @@ +% MTP2 Link State Control according to Q.703 Figure 3 / Figure 8 + +% (C) 2011-2012 by Harald Welte <laforge@gnumonks.org> +% +% All Rights Reserved +% +% This program is free software; you can redistribute it and/or modify +% it under the terms of the GNU Affero General Public License as +% published by the Free Software Foundation; either version 3 of the +% License, or (at your option) any later version. +% +% This program is distributed in the hope that it will be useful, +% but WITHOUT ANY WARRANTY; without even the implied warranty of +% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +% GNU General Public License for more details. +% +% You should have received a copy of the GNU Affero General Public License +% along with this program. If not, see <http://www.gnu.org/licenses/>. + +-module(mtp2_lsc). +-author('Harald Welte <laforge@gnumonks.org>'). +-behaviour(gen_fsm). + +% gen_fsm exports +-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]). + +% individual FSM states +-export([power_off/2, out_of_service/2, initial_alignment/2, + aligned_not_ready/2, aligned_ready/2, in_service/2, + processor_outage/2]). + +% sync event handlers +-export([power_off/3]). + +-record(lsc_state, { + t1_timeout, + t1, + iac_pid, + aerm_pid, + l3_pid, + poc_pid, + txc_pid, + local_proc_out, + proc_out, + emergency + }). + +-define(M2PA_T1_DEF, 300000). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% gen_fsm callbacks +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +init([Aerm, Txc, L3, Poc]) -> + {ok, Iac} = gen_fsm:start_link(mtp2_iac, [self(), Aerm, Txc], [{debug, [trace]}]), + LscState = #lsc_state{t1_timeout = ?M2PA_T1_DEF, + iac_pid = Iac, + aerm_pid = Aerm, + l3_pid = L3, + poc_pid = L3, + txc_pid = Txc, + local_proc_out = 0, + proc_out = 0, + emergency = 0}, + {ok, power_off, LscState}. + +terminate(Reason, State, _LoopDat) -> + io:format("Terminating ~p in State ~p (Reason: ~p)~n", + [?MODULE, State, Reason]), + ok. + +code_change(_OldVsn, StateName, LoopDat, _Extra) -> + {ok, StateName, LoopDat}. + +handle_event(Event, State, LoopDat) -> + io:format("Unknown Event ~p in state ~p~n", [Event, State]), + {next_state, State, LoopDat}. + + +handle_info(Info, State, LoopDat) -> + io:format("Unknown Info ~p in state ~p~n", [Info, State]), + {next_state, State, LoopDat}. + + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: power_off +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +power_off(power_on, LoopDat) -> + % Power On from MGMT + send_to(txc, start, LoopDat), + send_to(txc, si_os, LoopDat), + send_to(aerm, set_ti_to_tin, LoopDat), + % Cancel local processor outage, cancel emergency + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}. + +power_off(get_iac_pid, From, LoopDat) -> + Iac = LoopDat#lsc_state.iac_pid, + {reply, {ok, Iac}, power_off, LoopDat}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: out_of_service +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +out_of_service(start, LoopDat) -> + % Start from L3 + send_to(rc, start, LoopDat), + send_to(txc, start, LoopDat), + case LoopDat#lsc_state.emergency of + 1 -> + send_to(iac, emergency, LoopDat); + _ -> + ok + end, + send_to(iac, start, LoopDat), + {next_state, initial_alignment, LoopDat}; + +out_of_service(retrieve_bsnt, LoopDat) -> + send_to(rc, retrieve_bsnt, LoopDat), + {next_state, out_of_service, LoopDat}; + +out_of_service(retrieval_request_and_fsnc, LoopDat) -> + send_to(txc, retrieval_request_and_fsnc, LoopDat), + {next_state, out_of_service, LoopDat}; + +out_of_service(emergency, LoopDat) -> + {next_state, out_of_service, LoopDat#lsc_state{emergency=1}}; + +out_of_service(emergency_ceases, LoopDat) -> + {next_state, out_of_service, LoopDat#lsc_state{emergency=0}}; + +out_of_service(What, LoopDat) when What == local_processor_outage; + What == level3_failure -> + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=1}}; + +out_of_service(local_processor_recovered, LoopDat) -> + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0}}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: initial_alignment +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +initial_alignment(What, LoopDat) when What == local_processor_outage; + What == level3_failure -> + {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=1}}; + +initial_alignment(local_processor_recovered, LoopDat) -> + {next_state, initial_alignment, LoopDat#lsc_state{local_proc_out=0}}; + +initial_alignment(emergency, LoopDat) -> + send_to(iac, emergency, LoopDat), + {next_state, initial_alignment, LoopDat#lsc_state{emergency=1}}; + +initial_alignment(alignment_complete, LoopDat) -> + send_to(suerm, start, LoopDat), + {ok, T1} = timer:apply_after(LoopDat#lsc_state.t1_timeout, + gen_fsm, send_event, + [self(), {timer_expired, t1}]), + case LoopDat#lsc_state.local_proc_out of + 1 -> + send_to(poc, local_processor_outage, LoopDat), + send_to(txc, si_po, LoopDat), + send_to(rc, reject_msu_fiso, LoopDat), + NextState = aligned_not_ready; + _ -> + send_to(txc, fisu, LoopDat), + send_to(rc, accept_msu_fiso, LoopDat), + NextState = aligned_ready + end, + {next_state, NextState, LoopDat#lsc_state{t1=T1}}; + +initial_alignment(stop, LoopDat) -> + send_to(iac, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +initial_alignment(link_failure, LoopDat) -> + send_to(l3, out_of_service, LoopDat), + send_to(iac, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +initial_alignment(alignment_not_possible, LoopDat) -> + send_to(rc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +% ignore +initial_alignment(What, LoopDat) when + What == si_n; What == si_e; What == si_o; What == si_os -> + {next_state, initial_alignment, LoopDat}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: aligned_ready +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +aligned_ready(SioOrSios, LoopDat) when SioOrSios == si_o; + SioOrSios == si_os; + SioOrSios == link_failure -> + timer:cancel(LoopDat#lsc_state.t1), + send_to(l3, out_of_service, LoopDat), + send_to(rc, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat}; + +aligned_ready(stop, LoopDat) -> + timer:cancel(LoopDat#lsc_state.t1), + send_to(rc, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat}; + +aligned_ready({timer_expired, t1}, LoopDat) -> + send_to(l3, out_of_service, LoopDat), + send_to(rc, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat}; + +aligned_ready(si_po, LoopDat) -> + timer:cancel(LoopDat#lsc_state.t1), + send_to(l3, remote_processor_outage, LoopDat), + send_to(poc, remote_processor_outage, LoopDat), + {next_state, processor_outage, LoopDat}; + +aligned_ready(fisu_msu_received, LoopDat) -> + send_to(l3, in_service, LoopDat), + timer:cancel(LoopDat#lsc_state.t1), + send_to(txc, msu, LoopDat), + {next_state, in_service, LoopDat}; +aligned_ready(What, LoopDat) when What == local_processor_outage; + What == level3_failure -> + send_to(poc, local_processor_outage, LoopDat), + send_to(txc, si_po, LoopDat), + send_to(rc, reject_msu_fiso, LoopDat), + {next_state, aligned_not_ready, LoopDat}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: aligned_not_ready +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +aligned_not_ready(Err, LoopDat) when Err == link_failure; + Err == si_o; + Err == si_os -> + timer:cancel(LoopDat#lsc_state.t1), + send_to(l3, out_of_service, LoopDat), + send_to(l3, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + send_to(poc, stop, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +aligned_not_ready(stop, LoopDat) -> + timer:cancel(LoopDat#lsc_state.t1), + send_to(l3, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + send_to(poc, stop, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +aligned_not_ready({timer_expired, t1}, LoopDat) -> + send_to(l3, stop, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(txc, si_os, LoopDat), + send_to(poc, stop, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{local_proc_out=0, emergency=0}}; + +aligned_not_ready(local_processor_recovered, LoopDat) -> + send_to(poc, local_processor_recovered, LoopDat), + send_to(txc, fisu, LoopDat), + send_to(rc, accept_msu_fisu, LoopDat), + {next_state, aligned_ready, LoopDat#lsc_state{local_proc_out=0}}; + +aligned_not_ready(fisu_msu_received, LoopDat) -> + send_to(l3, in_service, LoopDat), + timer:cancel(LoopDat#lsc_state.t1), + {next_state, processor_outage, LoopDat}; + +aligned_not_ready(si_po, LoopDat) -> + send_to(l3, remote_processor_outage, LoopDat), + send_to(poc, remote_processor_outage, LoopDat), + timer:cancel(LoopDat#lsc_state.t1), + {next_state, processor_outage, LoopDat}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: in_service +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +in_service(What, LoopDat) when What == link_failure; + What == si_o; + What == si_n; + What == si_e; + What == si_os -> + send_to(l3, out_of_service, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{emergency=0}}; + +in_service(stop, LoopDat) -> + send_to(suerm, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{emergency=0}}; + +in_service(What, LoopDat) when What == local_processor_outage; + What == level3_failure -> + send_to(poc, local_processor_outage, LoopDat), + send_to(txc, si_po, LoopDat), + send_to(rc, reject_msu_fisu, LoopDat), + {next_state, aligned_not_ready, LoopDat#lsc_state{local_proc_out=1}}; + +in_service(si_po, LoopDat) -> + send_to(txc, fisu, LoopDat), + send_to(l3, remote_processor_outage, LoopDat), + send_to(poc, remote_processor_outage, LoopDat), + {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% STATE: processor_outage +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +processor_outage(retrieval_request_and_fsnc, LoopDat) -> + send_to(txc, retrieval_request_and_fsnc, LoopDat), + {next_state, processor_outage, LoopDat}; + +processor_outage(fisu_msu_received, LoopDat) -> + send_to(poc, remote_processor_recovered, LoopDat), + send_to(l3, remote_processor_recovered, LoopDat), + {next_state, processor_outage, LoopDat}; + +processor_outage(retrieve_bsnt, LoopDat) -> + send_to(rc, retrieve_bsnt, LoopDat), + {next_state, processor_outage, LoopDat}; + +processor_outage(What, LoopDat) when What == local_processor_outage; + What == level3_failure -> + send_to(poc, local_processor_outage, LoopDat), + send_to(txc, si_po, LoopDat), + {next_state, processor_outage, LoopDat#lsc_state{local_proc_out=1}}; + +processor_outage(si_po, LoopDat) -> + send_to(l3, remote_processor_outage, LoopDat), + send_to(poc, remote_processor_outage, LoopDat), + {next_state, processor_outage, LoopDat#lsc_state{proc_out=1}}; + +processor_outage(local_processor_recovered, LoopDat) -> + send_to(poc, local_processor_recovered, LoopDat), + send_to(rc, retrieve_fsnx, LoopDat), + send_to(txc, fisu, LoopDat), + {next_state, processor_outage, LoopDat}; + +processor_outage(flush_buffers, LoopDat) -> + send_to(txc, flush_buffers, LoopDat), + % FIXME: mark L3 ind recv + {next_state, processor_outage, LoopDat}; + +processor_outage(no_processor_outage, LoopDat) -> + % FIXME: check L3 ind + send_to(txc, msu, LoopDat), + send_to(rc, accept_msu_fisu, LoopDat), + {next_state, in_service, LoopDat#lsc_state{local_proc_out=0, proc_out=0}}; + +processor_outage(What, LoopDat) when What == link_failure; + What == si_o; + What == si_n; + What == si_e; + What == si_os -> + send_to(l3, out_of_service, LoopDat), + send_to(suerm, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(poc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}; + +processor_outage(stop, LoopDat) -> + send_to(suerm, stop, LoopDat), + send_to(rc, stop, LoopDat), + send_to(poc, stop, LoopDat), + send_to(txc, si_os, LoopDat), + {next_state, out_of_service, LoopDat#lsc_state{emergency=0, local_proc_out=0}}. + + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +% helper functions +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +send_to(txc, What, #lsc_state{txc_pid = Txc}) -> + Txc ! {lsc_txc, What}; +send_to(iac, What, #lsc_state{iac_pid = Iac}) -> + gen_fsm:send_event(Iac, What); +send_to(Who, What, _LoopDat) -> + io:format("Not sending LSC -> ~p: ~p~n", [Who, What]). + |