blob: 376f00f2493b37a379e038a8a02fbafc3d806594 [file] [log] [blame]
Harald Welte26bdef22012-01-16 22:22:17 +01001% M2PA in accordance with RFC4165 (http://tools.ietf.org/html/rfc4665)
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 Welte26bdef22012-01-16 22:22:17 +010033
34-module(sctp_m2pa).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(sctp_core).
37
38-include_lib("kernel/include/inet_sctp.hrl").
39-include("osmo_util.hrl").
40-include("m2pa.hrl").
41
42-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
43
Harald Welte91b79652012-01-17 10:12:34 +010044-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
Harald Welte26bdef22012-01-16 22:22:17 +010045
46-record(m2pa_state, {
47 last_bsn_received,
48 last_fsn_sent,
49 lsc_pid,
Harald Welte9ebf3162012-01-20 02:02:25 +010050 iac_pid,
51 msu_fisu_accepted
Harald Welte26bdef22012-01-16 22:22:17 +010052 }).
53
54%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
55% gen_fsm callbacks
56%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
57
58init(_InitOpts) ->
59 % start MTP2 IAC FSM pointing LSC, AERM and TXC to us
Harald Welte9ebf3162012-01-20 02:02:25 +010060 {ok, Lsc} = gen_fsm:start_link(mtp2_lsc, [self(), self(), self(), self(),self()], [{debug, [trace]}]),
Harald Welte26bdef22012-01-16 22:22:17 +010061 {ok, Iac} = gen_fsm:sync_send_event(Lsc, get_iac_pid),
62 gen_fsm:send_event(Lsc, power_on),
63 {ok, #m2pa_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff,
Harald Welte9ebf3162012-01-20 02:02:25 +010064 lsc_pid=Lsc, iac_pid=Iac,
65 msu_fisu_accepted = 0}}.
Harald Welte26bdef22012-01-16 22:22:17 +010066
67terminate(Reason, _State, _LoopDat) ->
68 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
69 ok.
70
71code_change(_OldVsn, _State, LoopDat, _Extra) ->
72 {ok, LoopDat}.
73
74handle_event(_Event, State, LoopDat) ->
75 {next_state, State, LoopDat}.
76
77handle_info({lsc_txc, What}, State, LoopDat) when
78 What == start; What == retrieval_request_and_fsnc ->
79 {next_state, State, LoopDat};
Harald Welte9ebf3162012-01-20 02:02:25 +010080handle_info({lsc_rc, accept_msu_fisu}, State, LoopDat) ->
81 {next_state, State, LoopDat#m2pa_state{msu_fisu_accepted = 1}};
82handle_info({lsc_rc, reject_msu_fisu}, State, LoopDat) ->
83 {next_state, State, LoopDat#m2pa_state{msu_fisu_accepted = 0}};
Harald Welte26bdef22012-01-16 22:22:17 +010084handle_info({Who, What}, established, LoopDat) when Who == iac_txc; Who == lsc_txc ->
85 Ls = iac_to_ls(What),
86 send_linkstate(Ls, LoopDat),
87 {next_state, established, LoopDat};
88handle_info(_Info, State, LoopDat) ->
89 {next_state, State, LoopDat}.
90
91%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
92% sctp_core callbacks
93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
94
Harald Welte91b79652012-01-17 10:12:34 +010095prim_up(Prim, State, LoopDat) ->
96 % default: forward all primitives to the user
97 {ok, Prim, LoopDat}.
98
99
Harald Welteb064a922012-01-19 23:18:34 +0100100% sctp_core indicates that we have received some data...
Harald Welte26bdef22012-01-16 22:22:17 +0100101rx_sctp(#sctp_sndrcvinfo{ppid = ?M2PA_PPID}, Data, State, LoopDat) ->
102 {ok, M2pa} = m2pa_codec:parse_msg(Data),
103 FsnRecv = M2pa#m2pa_msg.fwd_seq_nr,
104 % FIXME: check sequenc number linearity
105 case M2pa of
106 #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA,
107 msg_type = ?M2PA_TYPE_USER} ->
108 Mtp3 = M2pa#m2pa_msg.mtp3,
Harald Welte9ebf3162012-01-20 02:02:25 +0100109 case LoopDat#m2pa_state.msu_fisu_accepted of
110 1 ->
111 LoopDat2 = LoopDat#m2pa_state{last_bsn_received = FsnRecv},
112 case Mtp3 of
113 undefined ->
114 ok;
115 _ ->
116 send_userdata_ack(LoopDat2)
117 end,
118 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, fisu_msu_received),
119 Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
120 {ok, Prim, LoopDat2};
Harald Welteb064a922012-01-19 23:18:34 +0100121 _ ->
Harald Welte9ebf3162012-01-20 02:02:25 +0100122 {ignore, LoopDat}
123 end;
Harald Welte26bdef22012-01-16 22:22:17 +0100124 #m2pa_msg{msg_type = ?M2PA_TYPE_LINK} ->
125 handle_linkstate(M2pa, LoopDat),
126 {ignore, LoopDat};
127 _ ->
128 % do something with link related msgs
129 io:format("M2PA Unknown message ~p in state ~p~n", [M2pa, State]),
130 {ignore, State, LoopDat}
131 end.
132
133% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
134mtp_xfer(Mtp3, LoopDat) ->
135 Fsn = inc_seq_nr(LoopDat#m2pa_state.last_fsn_sent),
136 M2pa = #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA,
137 msg_type = ?M2PA_TYPE_USER,
138 fwd_seq_nr = Fsn,
139 back_seq_nr = LoopDat#m2pa_state.last_bsn_received,
140 mtp3 = Mtp3},
141 M2paBin = m2pa_codec:encode_msg(M2pa),
142 LoopDat2 = LoopDat#m2pa_state{last_fsn_sent = Fsn},
143 tx_sctp(?M2PA_STREAM_USER, M2paBin),
144 LoopDat2.
145
146state_change(_, established, LoopDat) ->
147 % emulate a 'start' from LSC
148 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start),
149 LoopDat;
150state_change(established, _, LoopDat) ->
151 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure),
152 LoopDat;
153state_change(_, _, LoopDat) ->
154 LoopDat.
155
156
157%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
158% helper functions
159%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
160
161inc_seq_nr(SeqNr) when is_integer(SeqNr) ->
162 SeqNr + 1 rem 16#FFFFFF.
163
164handle_linkstate(M2pa, LoopDat) when is_record(M2pa, m2pa_msg) ->
165 Linkstate = proplists:get_value(link_state, M2pa#m2pa_msg.parameters),
166 LsMtp2 = ls_to_iac(Linkstate),
167 if LsMtp2 == fisu ->
Harald Welte9ebf3162012-01-20 02:02:25 +0100168 case LoopDat#m2pa_state.msu_fisu_accepted of
169 1 ->
170 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid,
171 fisu_msu_received);
172 0 -> ok
173 end;
Harald Welte26bdef22012-01-16 22:22:17 +0100174 LsMtp2 == si_po ->
175 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, LsMtp2);
176 LsMtp2 == si_n; LsMtp2 == si_e; LsMtp2 == si_o; LsMtp2 == si_os ->
Harald Welte70984972012-01-19 22:50:39 +0100177 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, LsMtp2)
178 % IAC will receive the event as pass-through from LSC
179 %gen_fsm:send_event(LoopDat#m2pa_state.iac_pid, LsMtp2)
Harald Welte26bdef22012-01-16 22:22:17 +0100180 end.
181
182% convert M2PA link state to MTP2
183ls_to_iac(?M2PA_LS_OOS) ->
184 si_os;
185ls_to_iac(?M2PA_LS_ALIGNMENT) ->
186 si_o;
187ls_to_iac(?M2PA_LS_PROVING_NORMAL) ->
188 si_n;
189ls_to_iac(?M2PA_LS_PROVING_EMERG) ->
190 si_e;
191ls_to_iac(?M2PA_LS_READY) ->
192 fisu;
193ls_to_iac(?M2PA_LS_PROC_OUTAGE) ->
194 si_po;
195ls_to_iac(?M2PA_LS_PROC_RECOVERED) ->
196 fisu;
197ls_to_iac(?M2PA_LS_BUSY) ->
198 si_b.
199% FIXME: what about BUSY_ENDED?
200
201
202% convert MTP2 link state to M2PA
203iac_to_ls(si_os) ->
204 ?M2PA_LS_OOS;
205iac_to_ls(si_o) ->
206 ?M2PA_LS_ALIGNMENT;
207iac_to_ls(si_n) ->
208 ?M2PA_LS_PROVING_NORMAL;
209iac_to_ls(si_e) ->
210 ?M2PA_LS_PROVING_EMERG;
211iac_to_ls(fisu) ->
212 ?M2PA_LS_READY;
213iac_to_ls(msu) ->
214 ?M2PA_LS_READY;
215iac_to_ls(si_po) ->
216 ?M2PA_LS_PROC_OUTAGE;
217iac_to_ls(si_b) ->
218 ?M2PA_LS_BUSY.
219
220% Chapter 4.1.2 of RFC4165
221ls_stream(?M2PA_LS_PROC_OUTAGE) ->
222 1;
223ls_stream(?M2PA_LS_PROC_RECOVERED) ->
224 1;
225ls_stream(Foo) when is_integer(Foo) ->
226 0.
227
228send_linkstate(Ls, LoopDat) when is_integer(Ls) ->
229 Stream = ls_stream(Ls),
230 M2pa = #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA,
231 msg_type = ?M2PA_TYPE_LINK,
232 fwd_seq_nr = LoopDat#m2pa_state.last_fsn_sent,
233 back_seq_nr = LoopDat#m2pa_state.last_bsn_received,
234 parameters = [{link_state, Ls}]},
235 M2paBin = m2pa_codec:encode_msg(M2pa),
236 tx_sctp(Stream, M2paBin),
237 LoopDat.
238
Harald Welteb064a922012-01-19 23:18:34 +0100239send_userdata_ack(LoopDat) ->
240 M2pa = #m2pa_msg{msg_class = ?M2PA_CLASS_M2PA,
241 msg_type = ?M2PA_TYPE_USER,
242 fwd_seq_nr = LoopDat#m2pa_state.last_fsn_sent,
243 back_seq_nr = LoopDat#m2pa_state.last_bsn_received},
244 M2paBin = m2pa_codec:encode_msg(M2pa),
245 tx_sctp(0, M2paBin).
246
Harald Welte26bdef22012-01-16 22:22:17 +0100247tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
248 Param = {Stream, ?M2PA_PPID, Payload},
249 % sent to 'ourselves' (behaviour master module)
250 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).