blob: 3167c81ea887b70b88fc06f259f48714be960cf5 [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}) ->
70 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
82init(InitOpts) ->
Harald Welte8a0ab002011-04-03 22:16:12 +020083 OpenOptsBase = [{active, once}, {reuseaddr, true}],
84 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
85 case LocalPort of
86 undefined ->
87 OpenOpts = OpenOptsBase;
88 _ ->
89 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
90 end,
91 {ok, SctpSock} = gen_sctp:open(OpenOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020092 LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
Harald Weltecb1c0682011-04-14 21:56:26 +020093 user_fun = proplists:get_value(user_fun, InitOpts),
94 user_args = proplists:get_value(user_args, InitOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020095 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Welte8a0ab002011-04-03 22:16:12 +020096 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
97 sctp_local_port = LocalPort},
Harald Welte3bf7cb62011-04-03 00:25:34 +020098 LoopDat2 = reconnect_sctp(LoopDat),
99 {ok, asp_down, LoopDat2}.
100
Harald Welteb2d3abf2011-04-04 11:26:11 +0200101terminate(Reason, _State, LoopDat) ->
102 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
103 gen_sctp:close(LoopDat#m3ua_state.sctp_sock).
104
105code_change(_OldVsn, StateName, StateData, _Extra) ->
106 {ok, StateName, StateData}.
107
Harald Welte3bf7cb62011-04-03 00:25:34 +0200108% Helper function to send data to the SCTP peer
Harald Weltecb1c0682011-04-14 21:56:26 +0200109send_sctp_to_peer(LoopDat, PktData, StreamId) when is_binary(PktData) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200110 #m3ua_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
Harald Weltecb1c0682011-04-14 21:56:26 +0200111 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = 3, stream = StreamId},
112 gen_sctp:send(Sock, SndRcvInfo, PktData).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200113
114% same as above, but for un-encoded #m3ua_msg{}
115send_sctp_to_peer(LoopDat, M3uaMsg) when is_record(M3uaMsg, m3ua_msg) ->
116 MsgBin = m3ua_codec:encode_m3ua_msg(M3uaMsg),
Harald Weltecb1c0682011-04-14 21:56:26 +0200117 StreamId = sctp_stream_for_m3ua(M3uaMsg),
118 send_sctp_to_peer(LoopDat, MsgBin, StreamId).
119
120% resolve the Stream ID depending on the m3ua_msg: 0 == management, 1 == trafic
121sctp_stream_for_m3ua(#m3ua_msg{msg_class = Class}) when
122 Class == ?M3UA_MSGC_TRANSFER ->
123 1;
124sctp_stream_for_m3ua(#m3ua_msg{}) ->
125 0.
Harald Welte3bf7cb62011-04-03 00:25:34 +0200126
Harald Weltee393ea82011-04-04 16:00:06 +0200127
128send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, m3ua_state), is_record(Prim, primitive) ->
Harald Weltecb1c0682011-04-14 21:56:26 +0200129 #m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
130 Fun(Prim, Args).
Harald Weltee393ea82011-04-04 16:00:06 +0200131
Harald Welte3bf7cb62011-04-03 00:25:34 +0200132% helper to send one of the up/down/act/inact management messages + start timer
133send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
134 % generate and send the respective message
135 Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
136 send_sctp_to_peer(LoopDat, Msg),
137 % start T(ack) timer and wait for ASP_UP_ACK
Harald Weltee393ea82011-04-04 16:00:06 +0200138 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte6fc5b292011-04-04 10:38:30 +0200139 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200140 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
141 {next_state, State, LoopDat#m3ua_state{t_ack = Tack}}.
142
143
Harald Welte3bf7cb62011-04-03 00:25:34 +0200144
Harald Welte6fc5b292011-04-04 10:38:30 +0200145handle_event(Event, State, LoopDat) ->
146 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
147 {next_state, State, LoopDat}.
148
149
150
151handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200152 _State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
153 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200154 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
Harald Welteb2d3abf2011-04-04 11:26:11 +0200155 inbound_streams = _InStreams, assoc_id = _AssocId} = SAC,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200156 case SacState of
157 comm_up ->
Harald Weltee393ea82011-04-04 16:00:06 +0200158 % primmitive to the user
159 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200160 LoopDat2 = LoopDat;
161 comm_lost ->
Harald Weltee393ea82011-04-04 16:00:06 +0200162 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200163 LoopDat2 = reconnect_sctp(LoopDat);
164 addr_unreachable ->
165 LoopDat2 = reconnect_sctp(LoopDat)
166 end,
167 inet:setopts(Socket, [{active, once}]),
168 {next_state, asp_down, LoopDat2};
169
Harald Welte6fc5b292011-04-04 10:38:30 +0200170handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200171 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltee393ea82011-04-04 16:00:06 +0200172 % process incoming SCTP data
Harald Welte6fc5b292011-04-04 10:38:30 +0200173 if Socket == LoopDat#m3ua_state.sctp_sock,
174 RemoteIp == LoopDat#m3ua_state.sctp_remote_ip,
175 RemotePort == LoopDat#m3ua_state.sctp_remote_port,
176 3 == Anc#sctp_sndrcvinfo.ppid ->
177 Ret = rx_sctp(Anc, Data, State, LoopDat);
178 true ->
179 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
180 Ret = {next_state, State, LoopDat}
181 end,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200182 inet:setopts(Socket, [{active, once}]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200183 Ret;
Harald Welte3bf7cb62011-04-03 00:25:34 +0200184
Harald Welte6fc5b292011-04-04 10:38:30 +0200185handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, _State, LoopDat)
Harald Welte3bf7cb62011-04-03 00:25:34 +0200186 when is_record(Data, sctp_shutdown_event) ->
187 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
188 inet:setopts(Socket, [{active, once}]),
189 {next_state, asp_down, LoopDat}.
190
191
192
193asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte6fc5b292011-04-04 10:38:30 +0200194 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200195 % M-ASP_UP.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200196 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200197asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
198 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
199
200asp_down(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
201 msg_type = ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200202 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200203 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200204 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200205 {next_state, asp_inactive, LoopDat};
206
207asp_down(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
208 rx_m3ua(M3uaMsg, asp_down, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200209
210
Harald Welte6fc5b292011-04-04 10:38:30 +0200211asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
212 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200213 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200214 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
215 [{?M3UA_IEI_TRAF_MODE_TYPE, <<0,0,0,1>>}]);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200216
217asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
218 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
219
220asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200221 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200222 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200223 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200224
225asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
226 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
227
228asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
229 msg_type = ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200230 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200231 % transition into ASP_ACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200232 % signal this to the user
233 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200234 {next_state, asp_active, LoopDat};
235
236asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
237 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200238 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200239 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200240 % signal this to the user
241 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200242 {next_state, asp_down, LoopDat};
243
244asp_inactive(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
245 rx_m3ua(M3uaMsg, asp_inactive, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200246
247
248
249asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
250 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200251 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200252 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200253 % signal this to the user
254 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200255 {next_state, asp_down, LoopDat};
256
257asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
258 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_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_INACTIVE
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_INACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200263 {next_state, asp_inactive, LoopDat};
264
265asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200266 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200267 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200268 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200269
270asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
271 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
272
273asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte6fc5b292011-04-04 10:38:30 +0200274 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200275 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200276 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200277
278asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
279 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
280
281asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
282 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200283 % MTP-TRANSFER.req from user app: Send message to remote peer
Harald Welte3bf7cb62011-04-03 00:25:34 +0200284 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
285 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
286 msg_type = ?M3UA_MSGT_XFR_DATA,
287 payload = OptList},
288 send_sctp_to_peer(LoopDat, Msg),
289 {next_state, asp_active, LoopDat};
290asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
291 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200292 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200293 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
Harald Welte7dadde82011-10-19 13:40:39 +0200294 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,Mtp3)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200295 {next_state, asp_active, LoopDat};
296asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
297 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
298 timer:cancel(LoopDat#m3ua_state.t_ack),
299 % transition to ASP_INACTIVE
300 {next_state, asp_inactive, LoopDat};
301
Harald Welte6fc5b292011-04-04 10:38:30 +0200302asp_active(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
303 rx_m3ua(M3uaMsg, asp_active, LoopDat).
304
305
Harald Weltee393ea82011-04-04 16:00:06 +0200306
Harald Welteb2d3abf2011-04-04 11:26:11 +0200307rx_sctp(_Anc, Data, State, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200308 M3uaMsg = m3ua_codec:parse_m3ua_msg(Data),
309 gen_fsm:send_event(self(), M3uaMsg),
310 {next_state, State, LoopDat}.
311
312
Harald Weltee393ea82011-04-04 16:00:06 +0200313
Harald Welte6fc5b292011-04-04 10:38:30 +0200314rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
315 msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
Harald Weltee393ea82011-04-04 16:00:06 +0200316 send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200317 {next_state, State, LoopDat};
318
319rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
320 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
321 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte6fc5b292011-04-04 10:38:30 +0200322 send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
323 {next_state, State, LoopDat};
324
Harald Weltee393ea82011-04-04 16:00:06 +0200325rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
326 msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
327 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
328 {next_state, State, LoopDat};
329
330rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
331 msg_type = MsgType, payload = Params}, State, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200332 % transform to classic MTP primitive and send up to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200333 Mtp = map_ssnm_to_mtp_prim(MsgType),
334 send_prim_to_user(LoopDat, Mtp),
335 {next_state, State, LoopDat};
336
Harald Welte6fc5b292011-04-04 10:38:30 +0200337rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
338 io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
339 {next_state, State, LoopDat}.
Harald Weltee393ea82011-04-04 16:00:06 +0200340
Harald Welteb6473702011-04-14 22:06:42 +0200341% Transform the M3UA SSNM messages into classic MTP primitives
Harald Weltee393ea82011-04-04 16:00:06 +0200342map_ssnm_to_mtp_prim(MsgType) ->
Harald Welte10d77cd2011-11-04 22:28:21 +0100343 Mtp = #primitive{subsystem = 'MTP', spec_name = indication},
Harald Weltee393ea82011-04-04 16:00:06 +0200344 case MsgType of
345 ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
346 ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
347 ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
348 ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
349 end.