blob: 9a596e6f39f035dff49980320be42cd183387a5c [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,
Harald Welte8a0ab002011-04-03 22:16:12 +020061 sctp_local_port,
Harald Welte3bf7cb62011-04-03 00:25:34 +020062 sctp_sock,
63 sctp_assoc_id
64 }).
65
66start_link(InitOpts) ->
67 gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]).
68
69reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
Harald Welte231ae0b2012-04-01 20:13:23 +020070 timer:sleep(1*1000),
Harald Welte3bf7cb62011-04-03 00:25:34 +020071 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
Harald Welte8a0ab002011-04-03 22:16:12 +020072 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
Harald Welte3bf7cb62011-04-03 00:25:34 +020073 case gen_sctp:connect(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
74 {sctp_initmsg, InitMsg}]) of
75 {ok, Assoc} ->
Harald Welte9544cab2011-04-04 17:03:23 +020076 send_prim_to_user(L, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +020077 L#m3ua_state{sctp_assoc_id = Assoc#sctp_assoc_change.assoc_id};
78 {error, Error } ->
Harald Welte6fc5b292011-04-04 10:38:30 +020079 io:format("SCTP Error ~p, reconnecting~n", [Error]),
Harald Welte3bf7cb62011-04-03 00:25:34 +020080 reconnect_sctp(L)
81 end.
82
83init(InitOpts) ->
Harald Welte8a0ab002011-04-03 22:16:12 +020084 OpenOptsBase = [{active, once}, {reuseaddr, true}],
85 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
86 case LocalPort of
87 undefined ->
88 OpenOpts = OpenOptsBase;
89 _ ->
90 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
91 end,
92 {ok, SctpSock} = gen_sctp:open(OpenOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020093 LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
Harald Weltecb1c0682011-04-14 21:56:26 +020094 user_fun = proplists:get_value(user_fun, InitOpts),
95 user_args = proplists:get_value(user_args, InitOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020096 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Welte8a0ab002011-04-03 22:16:12 +020097 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
98 sctp_local_port = LocalPort},
Harald Welte3bf7cb62011-04-03 00:25:34 +020099 LoopDat2 = reconnect_sctp(LoopDat),
100 {ok, asp_down, LoopDat2}.
101
Harald Welteb2d3abf2011-04-04 11:26:11 +0200102terminate(Reason, _State, LoopDat) ->
103 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
104 gen_sctp:close(LoopDat#m3ua_state.sctp_sock).
105
106code_change(_OldVsn, StateName, StateData, _Extra) ->
107 {ok, StateName, StateData}.
108
Harald Welte3bf7cb62011-04-03 00:25:34 +0200109% Helper function to send data to the SCTP peer
Harald Weltecb1c0682011-04-14 21:56:26 +0200110send_sctp_to_peer(LoopDat, PktData, StreamId) when is_binary(PktData) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200111 #m3ua_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
Harald Weltecb1c0682011-04-14 21:56:26 +0200112 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = 3, stream = StreamId},
113 gen_sctp:send(Sock, SndRcvInfo, PktData).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200114
115% same as above, but for un-encoded #m3ua_msg{}
116send_sctp_to_peer(LoopDat, M3uaMsg) when is_record(M3uaMsg, m3ua_msg) ->
117 MsgBin = m3ua_codec:encode_m3ua_msg(M3uaMsg),
Harald Weltecb1c0682011-04-14 21:56:26 +0200118 StreamId = sctp_stream_for_m3ua(M3uaMsg),
119 send_sctp_to_peer(LoopDat, MsgBin, StreamId).
120
121% resolve the Stream ID depending on the m3ua_msg: 0 == management, 1 == trafic
122sctp_stream_for_m3ua(#m3ua_msg{msg_class = Class}) when
123 Class == ?M3UA_MSGC_TRANSFER ->
124 1;
125sctp_stream_for_m3ua(#m3ua_msg{}) ->
126 0.
Harald Welte3bf7cb62011-04-03 00:25:34 +0200127
Harald Weltee393ea82011-04-04 16:00:06 +0200128
129send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, m3ua_state), is_record(Prim, primitive) ->
Harald Weltecb1c0682011-04-14 21:56:26 +0200130 #m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
131 Fun(Prim, Args).
Harald Weltee393ea82011-04-04 16:00:06 +0200132
Harald Welte3bf7cb62011-04-03 00:25:34 +0200133% helper to send one of the up/down/act/inact management messages + start timer
134send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
135 % generate and send the respective message
136 Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
137 send_sctp_to_peer(LoopDat, Msg),
138 % start T(ack) timer and wait for ASP_UP_ACK
Harald Weltee393ea82011-04-04 16:00:06 +0200139 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte6fc5b292011-04-04 10:38:30 +0200140 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200141 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
142 {next_state, State, LoopDat#m3ua_state{t_ack = Tack}}.
143
144
Harald Welte3bf7cb62011-04-03 00:25:34 +0200145
Harald Welte6fc5b292011-04-04 10:38:30 +0200146handle_event(Event, State, LoopDat) ->
147 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
148 {next_state, State, LoopDat}.
149
150
151
152handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200153 _State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
154 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200155 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
Harald Welteb2d3abf2011-04-04 11:26:11 +0200156 inbound_streams = _InStreams, assoc_id = _AssocId} = SAC,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200157 case SacState of
158 comm_up ->
Harald Weltee393ea82011-04-04 16:00:06 +0200159 % primmitive to the user
160 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200161 LoopDat2 = LoopDat;
162 comm_lost ->
Harald Weltee393ea82011-04-04 16:00:06 +0200163 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200164 LoopDat2 = reconnect_sctp(LoopDat);
Harald Weltea0d2d962013-06-18 18:04:18 +0200165 shutdown_comp ->
166 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
167 LoopDat2 = reconnect_sctp(LoopDat);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200168 addr_unreachable ->
169 LoopDat2 = reconnect_sctp(LoopDat)
170 end,
171 inet:setopts(Socket, [{active, once}]),
172 {next_state, asp_down, LoopDat2};
173
Harald Welte6fc5b292011-04-04 10:38:30 +0200174handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200175 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltee393ea82011-04-04 16:00:06 +0200176 % process incoming SCTP data
Harald Welte6fc5b292011-04-04 10:38:30 +0200177 if Socket == LoopDat#m3ua_state.sctp_sock,
178 RemoteIp == LoopDat#m3ua_state.sctp_remote_ip,
179 RemotePort == LoopDat#m3ua_state.sctp_remote_port,
180 3 == Anc#sctp_sndrcvinfo.ppid ->
181 Ret = rx_sctp(Anc, Data, State, LoopDat);
182 true ->
183 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
184 Ret = {next_state, State, LoopDat}
185 end,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200186 inet:setopts(Socket, [{active, once}]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200187 Ret;
Harald Welte3bf7cb62011-04-03 00:25:34 +0200188
Harald Welte6fc5b292011-04-04 10:38:30 +0200189handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, _State, LoopDat)
Harald Welte3bf7cb62011-04-03 00:25:34 +0200190 when is_record(Data, sctp_shutdown_event) ->
191 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
192 inet:setopts(Socket, [{active, once}]),
193 {next_state, asp_down, LoopDat}.
194
195
196
197asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte6fc5b292011-04-04 10:38:30 +0200198 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200199 % M-ASP_UP.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200200 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200201asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
202 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
203
204asp_down(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
205 msg_type = ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200206 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200207 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200208 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200209 {next_state, asp_inactive, LoopDat};
210
211asp_down(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
212 rx_m3ua(M3uaMsg, asp_down, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200213
214
Harald Welte6fc5b292011-04-04 10:38:30 +0200215asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
216 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200217 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200218 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
219 [{?M3UA_IEI_TRAF_MODE_TYPE, <<0,0,0,1>>}]);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200220
221asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
222 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
223
224asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200225 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200226 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200227 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200228
229asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
230 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
231
232asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
233 msg_type = ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200234 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200235 % transition into ASP_ACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200236 % signal this to the user
237 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200238 {next_state, asp_active, LoopDat};
239
240asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
241 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200242 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200243 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200244 % signal this to the user
245 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200246 {next_state, asp_down, LoopDat};
247
248asp_inactive(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
249 rx_m3ua(M3uaMsg, asp_inactive, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200250
251
252
253asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
254 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200255 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200256 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200257 % signal this to the user
258 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200259 {next_state, asp_down, LoopDat};
260
261asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
262 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200263 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200264 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200265 % signal this to the user
266 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200267 {next_state, asp_inactive, LoopDat};
268
269asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200270 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200271 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200272 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200273
274asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
275 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
276
277asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte6fc5b292011-04-04 10:38:30 +0200278 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200279 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200280 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200281
282asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
283 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
284
285asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
286 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200287 % MTP-TRANSFER.req from user app: Send message to remote peer
Harald Welte3bf7cb62011-04-03 00:25:34 +0200288 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
289 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
290 msg_type = ?M3UA_MSGT_XFR_DATA,
291 payload = OptList},
292 send_sctp_to_peer(LoopDat, Msg),
293 {next_state, asp_active, LoopDat};
294asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
295 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200296 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200297 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
Harald Welte7dadde82011-10-19 13:40:39 +0200298 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,Mtp3)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200299 {next_state, asp_active, LoopDat};
300asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
301 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
302 timer:cancel(LoopDat#m3ua_state.t_ack),
303 % transition to ASP_INACTIVE
304 {next_state, asp_inactive, LoopDat};
305
Harald Welte6fc5b292011-04-04 10:38:30 +0200306asp_active(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
307 rx_m3ua(M3uaMsg, asp_active, LoopDat).
308
309
Harald Weltee393ea82011-04-04 16:00:06 +0200310
Harald Welteb2d3abf2011-04-04 11:26:11 +0200311rx_sctp(_Anc, Data, State, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200312 M3uaMsg = m3ua_codec:parse_m3ua_msg(Data),
313 gen_fsm:send_event(self(), M3uaMsg),
314 {next_state, State, LoopDat}.
315
316
Harald Weltee393ea82011-04-04 16:00:06 +0200317
Harald Welte6fc5b292011-04-04 10:38:30 +0200318rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
319 msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
Harald Weltee393ea82011-04-04 16:00:06 +0200320 send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200321 {next_state, State, LoopDat};
322
323rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
324 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
325 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte6fc5b292011-04-04 10:38:30 +0200326 send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
327 {next_state, State, LoopDat};
328
Harald Weltee393ea82011-04-04 16:00:06 +0200329rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
330 msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
331 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
332 {next_state, State, LoopDat};
333
334rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
335 msg_type = MsgType, payload = Params}, State, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200336 % transform to classic MTP primitive and send up to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200337 Mtp = map_ssnm_to_mtp_prim(MsgType),
338 send_prim_to_user(LoopDat, Mtp),
339 {next_state, State, LoopDat};
340
Harald Welte6fc5b292011-04-04 10:38:30 +0200341rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
342 io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
343 {next_state, State, LoopDat}.
Harald Weltee393ea82011-04-04 16:00:06 +0200344
Harald Welteb6473702011-04-14 22:06:42 +0200345% Transform the M3UA SSNM messages into classic MTP primitives
Harald Weltee393ea82011-04-04 16:00:06 +0200346map_ssnm_to_mtp_prim(MsgType) ->
Harald Welte10d77cd2011-11-04 22:28:21 +0100347 Mtp = #primitive{subsystem = 'MTP', spec_name = indication},
Harald Weltee393ea82011-04-04 16:00:06 +0200348 case MsgType of
349 ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
350 ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
351 ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
352 ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
353 end.