blob: 2adc4242daa7c40381c4e2673bf3a25e7a50b17b [file] [log] [blame]
Harald Welte3bf7cb62011-04-03 00:25:34 +02001% M3UA in accordance with RFC4666 (http://tools.ietf.org/html/rfc4666)
2
3% (C) 2011 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 Welte3bf7cb62011-04-03 00:25:34 +020033
34-module(m3ua_core).
35-author('Harald Welte <laforge@gnumonks.org>').
Harald Welteead1ba12011-04-15 10:20:04 +020036-behaviour(gen_fsm).
Harald Welte3bf7cb62011-04-03 00:25:34 +020037
38-include_lib("kernel/include/inet_sctp.hrl").
Harald Weltee393ea82011-04-04 16:00:06 +020039-include("osmo_util.hrl").
Harald Welte3bf7cb62011-04-03 00:25:34 +020040-include("sccp.hrl").
41-include("m3ua.hrl").
42
43-export([start_link/1]).
44
Harald Welteb2d3abf2011-04-04 11:26:11 +020045-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
Harald Welte3bf7cb62011-04-03 00:25:34 +020046
47% FSM states:
48-export([asp_down/2, asp_inactive/2, asp_active/2]).
49
50-define(T_ACK_TIMEOUT, 2*60*100).
51
52% Loop Data
53-record(m3ua_state, {
54 role, % asp | sgp
55 asp_state, % down, inactive, active
56 t_ack,
Harald Weltecb1c0682011-04-14 21:56:26 +020057 user_fun,
58 user_args,
Harald Welte3bf7cb62011-04-03 00:25:34 +020059 sctp_remote_ip,
60 sctp_remote_port,
61 sctp_sock,
62 sctp_assoc_id
63 }).
64
65start_link(InitOpts) ->
66 gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]).
67
68reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
Harald Welte231ae0b2012-04-01 20:13:23 +020069 timer:sleep(1*1000),
Harald Welte3bf7cb62011-04-03 00:25:34 +020070 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
Harald Welte8a0ab002011-04-03 22:16:12 +020071 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
Harald Welte3bf7cb62011-04-03 00:25:34 +020072 case gen_sctp:connect(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
73 {sctp_initmsg, InitMsg}]) of
74 {ok, Assoc} ->
Harald Welte9544cab2011-04-04 17:03:23 +020075 send_prim_to_user(L, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +020076 L#m3ua_state{sctp_assoc_id = Assoc#sctp_assoc_change.assoc_id};
77 {error, Error } ->
Harald Welte6fc5b292011-04-04 10:38:30 +020078 io:format("SCTP Error ~p, reconnecting~n", [Error]),
Harald Welte3bf7cb62011-04-03 00:25:34 +020079 reconnect_sctp(L)
80 end.
81
Harald Welte48c07f02013-09-08 22:22:01 +020082build_openopt({sctp_local_port, Port}) ->
83 {port, Port};
84build_openopt({sctp_local_ip, undefined}) ->
85 [];
86build_openopt({sctp_local_ip, Ip}) ->
87 {ip, Ip};
88build_openopt(_) ->
89 [].
90build_openopts(PropList) ->
91 [{active, once}, {reuseaddr, true}] ++
92 lists:flatten(lists:map(fun build_openopt/1, PropList)).
93
Harald Welte3bf7cb62011-04-03 00:25:34 +020094init(InitOpts) ->
Harald Welte48c07f02013-09-08 22:22:01 +020095 {ok, SctpSock} = gen_sctp:open(build_openopts(InitOpts)),
Harald Welte3bf7cb62011-04-03 00:25:34 +020096 LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
Harald Weltecb1c0682011-04-14 21:56:26 +020097 user_fun = proplists:get_value(user_fun, InitOpts),
98 user_args = proplists:get_value(user_args, InitOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020099 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Welte48c07f02013-09-08 22:22:01 +0200100 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts)},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200101 LoopDat2 = reconnect_sctp(LoopDat),
102 {ok, asp_down, LoopDat2}.
103
Harald Welteb2d3abf2011-04-04 11:26:11 +0200104terminate(Reason, _State, LoopDat) ->
105 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
106 gen_sctp:close(LoopDat#m3ua_state.sctp_sock).
107
108code_change(_OldVsn, StateName, StateData, _Extra) ->
109 {ok, StateName, StateData}.
110
Harald Welte3bf7cb62011-04-03 00:25:34 +0200111% Helper function to send data to the SCTP peer
Harald Weltecb1c0682011-04-14 21:56:26 +0200112send_sctp_to_peer(LoopDat, PktData, StreamId) when is_binary(PktData) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200113 #m3ua_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
Harald Weltecb1c0682011-04-14 21:56:26 +0200114 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = 3, stream = StreamId},
115 gen_sctp:send(Sock, SndRcvInfo, PktData).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200116
117% same as above, but for un-encoded #m3ua_msg{}
118send_sctp_to_peer(LoopDat, M3uaMsg) when is_record(M3uaMsg, m3ua_msg) ->
119 MsgBin = m3ua_codec:encode_m3ua_msg(M3uaMsg),
Harald Weltecb1c0682011-04-14 21:56:26 +0200120 StreamId = sctp_stream_for_m3ua(M3uaMsg),
121 send_sctp_to_peer(LoopDat, MsgBin, StreamId).
122
123% resolve the Stream ID depending on the m3ua_msg: 0 == management, 1 == trafic
124sctp_stream_for_m3ua(#m3ua_msg{msg_class = Class}) when
125 Class == ?M3UA_MSGC_TRANSFER ->
126 1;
127sctp_stream_for_m3ua(#m3ua_msg{}) ->
128 0.
Harald Welte3bf7cb62011-04-03 00:25:34 +0200129
Harald Weltee393ea82011-04-04 16:00:06 +0200130
131send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, m3ua_state), is_record(Prim, primitive) ->
Harald Weltecb1c0682011-04-14 21:56:26 +0200132 #m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
133 Fun(Prim, Args).
Harald Weltee393ea82011-04-04 16:00:06 +0200134
Harald Welte3bf7cb62011-04-03 00:25:34 +0200135% helper to send one of the up/down/act/inact management messages + start timer
136send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
137 % generate and send the respective message
138 Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
139 send_sctp_to_peer(LoopDat, Msg),
140 % start T(ack) timer and wait for ASP_UP_ACK
Harald Weltee393ea82011-04-04 16:00:06 +0200141 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte6fc5b292011-04-04 10:38:30 +0200142 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200143 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
144 {next_state, State, LoopDat#m3ua_state{t_ack = Tack}}.
145
146
Harald Welte3bf7cb62011-04-03 00:25:34 +0200147
Harald Welte6fc5b292011-04-04 10:38:30 +0200148handle_event(Event, State, LoopDat) ->
149 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
150 {next_state, State, LoopDat}.
151
152
153
154handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200155 _State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
156 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200157 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
Harald Welteb2d3abf2011-04-04 11:26:11 +0200158 inbound_streams = _InStreams, assoc_id = _AssocId} = SAC,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200159 case SacState of
160 comm_up ->
Harald Weltee393ea82011-04-04 16:00:06 +0200161 % primmitive to the user
162 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200163 LoopDat2 = LoopDat;
164 comm_lost ->
Harald Weltee393ea82011-04-04 16:00:06 +0200165 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200166 LoopDat2 = reconnect_sctp(LoopDat);
Harald Weltea0d2d962013-06-18 18:04:18 +0200167 shutdown_comp ->
168 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
169 LoopDat2 = reconnect_sctp(LoopDat);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200170 addr_unreachable ->
171 LoopDat2 = reconnect_sctp(LoopDat)
172 end,
173 inet:setopts(Socket, [{active, once}]),
174 {next_state, asp_down, LoopDat2};
175
Harald Weltea5dfd5b2013-07-15 11:27:10 +0200176handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SPC}},
177 State, LoopDat) when is_record(SPC, sctp_paddr_change) ->
178 io:format("SCTP Peer address change ~p ~p~n", [ANC, SPC]),
179 {NewState, LoopDat2} = case SPC#sctp_paddr_change.state of
180 addr_available ->
181 % we don't care
182 {State, LoopDat};
183 addr_unreachable ->
184 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
185 {asp_down, reconnect_sctp(LoopDat)};
186 addr_removed ->
187 % FIXME: what if the last one is removed
188 {State, LoopDat};
189 addr_added ->
190 % we don't care
191 {State, LoopDat};
192 addr_made_prim ->
193 % FIXME: do we need to change remote_ip in our LoopDat?
194 {State, LoopDat}
195 end,
196 inet:setopts(Socket, [{active, once}]),
197 {next_state, NewState, LoopDat2};
198
Harald Welte6fc5b292011-04-04 10:38:30 +0200199handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200200 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltee393ea82011-04-04 16:00:06 +0200201 % process incoming SCTP data
Harald Welte6fc5b292011-04-04 10:38:30 +0200202 if Socket == LoopDat#m3ua_state.sctp_sock,
203 RemoteIp == LoopDat#m3ua_state.sctp_remote_ip,
204 RemotePort == LoopDat#m3ua_state.sctp_remote_port,
205 3 == Anc#sctp_sndrcvinfo.ppid ->
206 Ret = rx_sctp(Anc, Data, State, LoopDat);
207 true ->
208 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
209 Ret = {next_state, State, LoopDat}
210 end,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200211 inet:setopts(Socket, [{active, once}]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200212 Ret;
Harald Welte3bf7cb62011-04-03 00:25:34 +0200213
Harald Welte6fc5b292011-04-04 10:38:30 +0200214handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, _State, LoopDat)
Harald Welte3bf7cb62011-04-03 00:25:34 +0200215 when is_record(Data, sctp_shutdown_event) ->
216 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
217 inet:setopts(Socket, [{active, once}]),
218 {next_state, asp_down, LoopDat}.
219
220
221
222asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte6fc5b292011-04-04 10:38:30 +0200223 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200224 % M-ASP_UP.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200225 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200226asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
227 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
228
229asp_down(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
230 msg_type = ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200231 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200232 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200233 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200234 {next_state, asp_inactive, LoopDat};
235
236asp_down(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
237 rx_m3ua(M3uaMsg, asp_down, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200238
239
Harald Welte6fc5b292011-04-04 10:38:30 +0200240asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
241 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200242 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200243 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
244 [{?M3UA_IEI_TRAF_MODE_TYPE, <<0,0,0,1>>}]);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200245
246asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
247 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
248
249asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200250 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200251 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200252 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200253
254asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
255 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
256
257asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
258 msg_type = ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200259 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200260 % transition into ASP_ACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200261 % signal this to the user
262 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200263 {next_state, asp_active, LoopDat};
264
265asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
266 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200267 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200268 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200269 % signal this to the user
270 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200271 {next_state, asp_down, LoopDat};
272
273asp_inactive(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
274 rx_m3ua(M3uaMsg, asp_inactive, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200275
276
277
278asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
279 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200280 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200281 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200282 % signal this to the user
283 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200284 {next_state, asp_down, LoopDat};
285
286asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
287 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200288 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200289 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200290 % signal this to the user
291 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200292 {next_state, asp_inactive, LoopDat};
293
294asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200295 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200296 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200297 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200298
299asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
300 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
301
302asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte6fc5b292011-04-04 10:38:30 +0200303 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200304 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200305 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200306
307asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
308 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
309
310asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
311 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200312 % MTP-TRANSFER.req from user app: Send message to remote peer
Harald Welte3bf7cb62011-04-03 00:25:34 +0200313 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
314 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
315 msg_type = ?M3UA_MSGT_XFR_DATA,
316 payload = OptList},
317 send_sctp_to_peer(LoopDat, Msg),
318 {next_state, asp_active, LoopDat};
319asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
320 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200321 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200322 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
Harald Welte7dadde82011-10-19 13:40:39 +0200323 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,Mtp3)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200324 {next_state, asp_active, LoopDat};
325asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
326 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
327 timer:cancel(LoopDat#m3ua_state.t_ack),
328 % transition to ASP_INACTIVE
329 {next_state, asp_inactive, LoopDat};
330
Harald Welte6fc5b292011-04-04 10:38:30 +0200331asp_active(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
332 rx_m3ua(M3uaMsg, asp_active, LoopDat).
333
334
Harald Weltee393ea82011-04-04 16:00:06 +0200335
Harald Welteb2d3abf2011-04-04 11:26:11 +0200336rx_sctp(_Anc, Data, State, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200337 M3uaMsg = m3ua_codec:parse_m3ua_msg(Data),
338 gen_fsm:send_event(self(), M3uaMsg),
339 {next_state, State, LoopDat}.
340
341
Harald Weltee393ea82011-04-04 16:00:06 +0200342
Harald Welte6fc5b292011-04-04 10:38:30 +0200343rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
344 msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
Harald Weltee393ea82011-04-04 16:00:06 +0200345 send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200346 {next_state, State, LoopDat};
347
348rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
349 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
350 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte6fc5b292011-04-04 10:38:30 +0200351 send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
352 {next_state, State, LoopDat};
353
Harald Weltee393ea82011-04-04 16:00:06 +0200354rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
355 msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
356 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
357 {next_state, State, LoopDat};
358
359rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
360 msg_type = MsgType, payload = Params}, State, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200361 % transform to classic MTP primitive and send up to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200362 Mtp = map_ssnm_to_mtp_prim(MsgType),
363 send_prim_to_user(LoopDat, Mtp),
364 {next_state, State, LoopDat};
365
Harald Welte6fc5b292011-04-04 10:38:30 +0200366rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
367 io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
368 {next_state, State, LoopDat}.
Harald Weltee393ea82011-04-04 16:00:06 +0200369
Harald Welteb6473702011-04-14 22:06:42 +0200370% Transform the M3UA SSNM messages into classic MTP primitives
Harald Weltee393ea82011-04-04 16:00:06 +0200371map_ssnm_to_mtp_prim(MsgType) ->
Harald Welte10d77cd2011-11-04 22:28:21 +0100372 Mtp = #primitive{subsystem = 'MTP', spec_name = indication},
Harald Weltee393ea82011-04-04 16:00:06 +0200373 case MsgType of
374 ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
375 ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
376 ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
377 ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
378 end.