blob: 9e879144263677d94666a6135ea636885e18c58c [file] [log] [blame]
Harald Welteee7964c2012-05-07 23:55:02 +02001% M2UA in accordance with RFC3331 (http://tools.ietf.org/html/rfc3331)
2
Harald Welte0d8af6b2013-07-27 15:02:17 +08003% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
Harald Welteee7964c2012-05-07 23:55:02 +02004%
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(sctp_m2ua).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behaviour(sctp_core).
23
24-include_lib("kernel/include/inet_sctp.hrl").
25-include("osmo_util.hrl").
Harald Weltee58b38f2012-05-30 12:05:18 +020026-include("xua.hrl").
Harald Welteee7964c2012-05-07 23:55:02 +020027-include("m2ua.hrl").
Harald Weltecf74df52013-08-26 17:29:28 +020028-include("mtp3.hrl").
Harald Welteee7964c2012-05-07 23:55:02 +020029
Harald Welte0d8af6b2013-07-27 15:02:17 +080030-define(M2UA_STREAM_USER, 1).
31
Harald Welteee7964c2012-05-07 23:55:02 +020032-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
33
34-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
35
36-record(m2ua_state, {
37 asp_pid,
38 last_bsn_received,
Harald Weltecf74df52013-08-26 17:29:28 +020039 last_fsn_sent,
40 role
Harald Welteee7964c2012-05-07 23:55:02 +020041 }).
42
43%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
44% gen_fsm callbacks
45%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
46
Harald Welte0d8af6b2013-07-27 15:02:17 +080047init([Role]) ->
48 Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
49 AsPid = undefined, % FIXME
50 % we use sua_asp module, as m2ua has no difference here
51 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self(), Role], [{debug, [trace]}]),
Harald Weltecf74df52013-08-26 17:29:28 +020052 {ok, #m2ua_state{last_bsn_received=16#ffffff,
53 last_fsn_sent=16#ffffff, asp_pid=Asp, role=Role}}.
Harald Welteee7964c2012-05-07 23:55:02 +020054
55terminate(Reason, _State, _LoopDat) ->
56 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
57 ok.
58
59code_change(_OldVsn, _State, LoopDat, _Extra) ->
60 {ok, LoopDat}.
61
62handle_event(_Event, State, LoopDat) ->
63 {next_state, State, LoopDat}.
64
65handle_info(_Info, State, LoopDat) ->
66 {next_state, State, LoopDat}.
67
68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69% sctp_core callbacks
70%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
71
72prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
Harald Welte0d8af6b2013-07-27 15:02:17 +080073 % confirmation in case of active/connect mode
Harald Welteee7964c2012-05-07 23:55:02 +020074 Asp = LoopDat#m2ua_state.asp_pid,
75 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
76 {ignore, LoopDat};
Harald Welte0d8af6b2013-07-27 15:02:17 +080077prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = indication}, State, LoopDat) ->
78 % indication in case of passive/listen mode
Harald Welte0d8af6b2013-07-27 15:02:17 +080079 {ignore, LoopDat};
Harald Welteee7964c2012-05-07 23:55:02 +020080prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
Harald Welte4540ecd2013-07-27 15:08:53 +080081 % confirmation in case of active/connect mode
Harald Welteee7964c2012-05-07 23:55:02 +020082 Asp = LoopDat#m2ua_state.asp_pid,
Harald Welte7ccc15e2013-08-27 10:27:52 +020083 % override mode, interface ID 1. FIXME: user-specify interface ID(s)
84 Pars = [{?M2UA_P_COM_TRAF_MODE_T, {4, 1}}, {?M2UA_P_COM_INTF_ID_INT, {4, 0}}],
85 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request,Pars)),
Harald Welteee7964c2012-05-07 23:55:02 +020086 {ignore, LoopDat};
Harald Welte4540ecd2013-07-27 15:08:53 +080087
Harald Welteee7964c2012-05-07 23:55:02 +020088prim_up(Prim, State, LoopDat) ->
Harald Weltecf74df52013-08-26 17:29:28 +020089 % default: forward all primitives to the user
Harald Welteee7964c2012-05-07 23:55:02 +020090 {ok, Prim, LoopDat}.
91
92
93% sctp_core indicates that we have received some data...
94rx_sctp(#sctp_sndrcvinfo{ppid = ?M2UA_PPID}, Data, State, LoopDat) ->
95 Asp = LoopDat#m2ua_state.asp_pid,
Harald Welte0d8af6b2013-07-27 15:02:17 +080096 M2ua = xua_codec:parse_msg(Data),
Harald Welteee7964c2012-05-07 23:55:02 +020097 % FIXME: check sequenc number linearity
98 case M2ua of
Harald Weltecf74df52013-08-26 17:29:28 +020099 #xua_msg{msg_class = ?M2UA_MSGC_ASPSM} ->
Harald Welteee7964c2012-05-07 23:55:02 +0200100 gen_fsm:send_event(Asp, M2ua),
101 {ignore, LoopDat};
Harald Weltecf74df52013-08-26 17:29:28 +0200102 #xua_msg{msg_class = ?M2UA_MSGC_ASPTM} ->
Harald Welteee7964c2012-05-07 23:55:02 +0200103 gen_fsm:send_event(Asp, M2ua),
104 {ignore, LoopDat};
Harald Weltee58b38f2012-05-30 12:05:18 +0200105 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
Harald Weltee58b38f2012-05-30 12:05:18 +0200106 msg_type = ?M2UA_MAUP_MSGT_CONG_IND} ->
107 % FIXME
108 error_logger:error_report(["unimplemented message",
109 {msg_type, "CONG_IND"}]),
110 {ignore, LoopDat};
111 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
112 msg_type = ?M2UA_MAUP_MSGT_DATA_RETR_REQ} ->
113 % FIXME
114 error_logger:error_report(["unimplemented message",
115 {msg_type, "RETR_REQ"}]),
116 {ignore, LoopDat};
117 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
118 msg_type = ?M2UA_MAUP_MSGT_DATA} ->
119 Mtp3 = proplists:get_value(?M2UA_P_M2UA_DATA1, M2ua#xua_msg.payload),
120 Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
Harald Welte0d8af6b2013-07-27 15:02:17 +0800121 {ok, Prim, LoopDat};
Harald Welteee7964c2012-05-07 23:55:02 +0200122 _ ->
Harald Weltecf74df52013-08-26 17:29:28 +0200123 rx_sctp(M2ua, State, LoopDat)
Harald Welteee7964c2012-05-07 23:55:02 +0200124 end.
125
Harald Weltecf74df52013-08-26 17:29:28 +0200126% SG side
127rx_sctp(#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
128 msg_type = ?M2UA_MAUP_MSGT_EST_REQ}, State,
129 LoopDat = #m2ua_state{role=sg}) ->
130 % FIXME: respond with M2UA_MAUP_MSGT_EST_CONF
131 error_logger:error_report(["unimplemented message",
132 {msg_type, "EST_REQ"}]),
133 {ignore, LoopDat};
134rx_sctp(#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
135 msg_type = ?M2UA_MAUP_MSGT_REL_REQ}, State,
136 LoopDat = #m2ua_state{role=sg}) ->
137 % FIXME: respond with M2UA_MAUP_MSGT_REL_CONF
138 error_logger:error_report(["unimplemented message",
139 {msg_type, "REL_REQ"}]),
140 {ignore, LoopDat};
141
142rx_sctp(M2ua = #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
143 msg_type = ?M2UA_MAUP_MSGT_STATE_REQ}, State,
144 LoopDat = #m2ua_state{role=sg}) ->
145 handle_m2ua_state_req(M2ua),
146 {ignore, LoopDat};
147
148% ASP side
149rx_sctp(#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
150 msg_type = ?M2UA_MAUP_MSGT_REL_CONF}, State,
151 LoopDat = #m2ua_state{role=asp}) ->
152 error_logger:error_report(["unimplemented message",
153 {msg_type, "REL_CONF"}]),
154 {ignore, LoopDat};
155
156rx_sctp(#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
157 msg_type = ?M2UA_MAUP_MSGT_EST_CONF}, State,
158 LoopDat = #m2ua_state{role=asp}) ->
159 error_logger:error_report(["unimplemented message",
160 {msg_type, "EST_CONF"}]),
161 {ignore, LoopDat};
162
163rx_sctp(M2ua = #xua_msg{}, State, LoopDat) ->
164 % do something with link rel msgs
165 io:format("M2UA Unknown message ~p in state ~p~n", [M2ua, State]),
166 {ignore, LoopDat}.
167
168
Harald Welteee7964c2012-05-07 23:55:02 +0200169% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
Harald Welte0d8af6b2013-07-27 15:02:17 +0800170mtp_xfer(M2ua, LoopDat) when is_record(M2ua, xua_msg) ->
171 M2uaBin = xua_codec:encode_msg(M2ua),
172 tx_sctp(?M2UA_STREAM_USER, M2uaBin),
173 LoopDat;
174
Harald Weltecf74df52013-08-26 17:29:28 +0200175mtp_xfer(Mtp3, LoopDat) when is_record(Mtp3, mtp3_msg) ->
176 MsgBin = mtp3_codec:encode_mtp3_msg(Mtp3),
177 mtp_xfer(MsgBin, LoopDat);
178
179mtp_xfer(Mtp3bin, LoopDat) when is_binary(Mtp3bin) ->
180 M2ua = #xua_msg{version = 1,
181 msg_class = ?M2UA_MSGC_MAUP,
Harald Weltee58b38f2012-05-30 12:05:18 +0200182 msg_type = ?M2UA_MAUP_MSGT_DATA,
Harald Weltecf74df52013-08-26 17:29:28 +0200183 payload = [{?M2UA_P_COM_INTF_ID_INT, {4, 0}},
184 {?M2UA_P_M2UA_DATA1, {byte_size(Mtp3bin), Mtp3bin}}]},
Harald Welte0d8af6b2013-07-27 15:02:17 +0800185 mtp_xfer(M2ua, LoopDat).
Harald Welteee7964c2012-05-07 23:55:02 +0200186
187state_change(_, established, LoopDat) ->
188 % emulate a 'start' from LSC
189 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start),
190 LoopDat;
191state_change(established, _, LoopDat) ->
192 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure),
193 LoopDat;
194state_change(_, _, LoopDat) ->
195 LoopDat.
196
Harald Weltee58b38f2012-05-30 12:05:18 +0200197handle_m2ua_state_req(M2ua = #xua_msg{payload = Payload}) ->
198 {?M2UA_P_MAUP_STATE, State} = lists:keyfind(?M2UA_P_MAUP_STATE, 1, Payload),
199 % FIXME handle_m2ua_state_req(State).
200 % LOP_SET/CLEAR, EMER_SET/CLEAR, FLUSH_BUFFERSm CONTINUE, CLEAR_RTB, AUDIT, CONG*
201 % FIXME: respond with M2UA_MAUP_MSGT_STATE_CONF
202 error_logger:error_report(["unimplemented message",
203 {msg_type, "STATE_REQ"}]),
204 true.
Harald Welteee7964c2012-05-07 23:55:02 +0200205
206%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
207% helper functions
208%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
209
210tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
211 Param = {Stream, ?M2UA_PPID, Payload},
212 % sent to 'ourselves' (behaviour master module)
213 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
Harald Welte0d8af6b2013-07-27 15:02:17 +0800214
215% callback fun for ASP FMS
216asp_prim_to_user(Prim, [SctpPid]) ->
217 gen_fsm:send_event(SctpPid, Prim).