blob: fa23b365871d762e22b273674a57745c619ab029 [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/>.
19
20-module(m3ua_core).
21-author('Harald Welte <laforge@gnumonks.org>').
22
23-include_lib("kernel/include/inet_sctp.hrl").
Harald Weltee393ea82011-04-04 16:00:06 +020024-include("osmo_util.hrl").
Harald Welte3bf7cb62011-04-03 00:25:34 +020025-include("sccp.hrl").
26-include("m3ua.hrl").
27
28-export([start_link/1]).
29
Harald Welteb2d3abf2011-04-04 11:26:11 +020030-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
Harald Welte3bf7cb62011-04-03 00:25:34 +020031
32% FSM states:
33-export([asp_down/2, asp_inactive/2, asp_active/2]).
34
35-define(T_ACK_TIMEOUT, 2*60*100).
36
37% Loop Data
38-record(m3ua_state, {
39 role, % asp | sgp
40 asp_state, % down, inactive, active
41 t_ack,
Harald Weltecb1c0682011-04-14 21:56:26 +020042 user_fun,
43 user_args,
Harald Welte3bf7cb62011-04-03 00:25:34 +020044 sctp_remote_ip,
45 sctp_remote_port,
Harald Welte8a0ab002011-04-03 22:16:12 +020046 sctp_local_port,
Harald Welte3bf7cb62011-04-03 00:25:34 +020047 sctp_sock,
48 sctp_assoc_id
49 }).
50
51start_link(InitOpts) ->
52 gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]).
53
54reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
55 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
Harald Welte8a0ab002011-04-03 22:16:12 +020056 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
Harald Welte3bf7cb62011-04-03 00:25:34 +020057 case gen_sctp:connect(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
58 {sctp_initmsg, InitMsg}]) of
59 {ok, Assoc} ->
Harald Welte9544cab2011-04-04 17:03:23 +020060 send_prim_to_user(L, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +020061 L#m3ua_state{sctp_assoc_id = Assoc#sctp_assoc_change.assoc_id};
62 {error, Error } ->
Harald Welte6fc5b292011-04-04 10:38:30 +020063 io:format("SCTP Error ~p, reconnecting~n", [Error]),
Harald Welte3bf7cb62011-04-03 00:25:34 +020064 reconnect_sctp(L)
65 end.
66
67init(InitOpts) ->
Harald Welte8a0ab002011-04-03 22:16:12 +020068 OpenOptsBase = [{active, once}, {reuseaddr, true}],
69 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
70 case LocalPort of
71 undefined ->
72 OpenOpts = OpenOptsBase;
73 _ ->
74 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
75 end,
76 {ok, SctpSock} = gen_sctp:open(OpenOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020077 LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
Harald Weltecb1c0682011-04-14 21:56:26 +020078 user_fun = proplists:get_value(user_fun, InitOpts),
79 user_args = proplists:get_value(user_args, InitOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020080 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Welte8a0ab002011-04-03 22:16:12 +020081 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
82 sctp_local_port = LocalPort},
Harald Welte3bf7cb62011-04-03 00:25:34 +020083 LoopDat2 = reconnect_sctp(LoopDat),
84 {ok, asp_down, LoopDat2}.
85
Harald Welteb2d3abf2011-04-04 11:26:11 +020086terminate(Reason, _State, LoopDat) ->
87 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
88 gen_sctp:close(LoopDat#m3ua_state.sctp_sock).
89
90code_change(_OldVsn, StateName, StateData, _Extra) ->
91 {ok, StateName, StateData}.
92
Harald Welte3bf7cb62011-04-03 00:25:34 +020093% Helper function to send data to the SCTP peer
Harald Weltecb1c0682011-04-14 21:56:26 +020094send_sctp_to_peer(LoopDat, PktData, StreamId) when is_binary(PktData) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +020095 #m3ua_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
Harald Weltecb1c0682011-04-14 21:56:26 +020096 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = 3, stream = StreamId},
97 gen_sctp:send(Sock, SndRcvInfo, PktData).
Harald Welte3bf7cb62011-04-03 00:25:34 +020098
99% same as above, but for un-encoded #m3ua_msg{}
100send_sctp_to_peer(LoopDat, M3uaMsg) when is_record(M3uaMsg, m3ua_msg) ->
101 MsgBin = m3ua_codec:encode_m3ua_msg(M3uaMsg),
Harald Weltecb1c0682011-04-14 21:56:26 +0200102 StreamId = sctp_stream_for_m3ua(M3uaMsg),
103 send_sctp_to_peer(LoopDat, MsgBin, StreamId).
104
105% resolve the Stream ID depending on the m3ua_msg: 0 == management, 1 == trafic
106sctp_stream_for_m3ua(#m3ua_msg{msg_class = Class}) when
107 Class == ?M3UA_MSGC_TRANSFER ->
108 1;
109sctp_stream_for_m3ua(#m3ua_msg{}) ->
110 0.
Harald Welte3bf7cb62011-04-03 00:25:34 +0200111
Harald Weltee393ea82011-04-04 16:00:06 +0200112
113send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, m3ua_state), is_record(Prim, primitive) ->
Harald Weltecb1c0682011-04-14 21:56:26 +0200114 #m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
115 Fun(Prim, Args).
Harald Weltee393ea82011-04-04 16:00:06 +0200116
Harald Welte3bf7cb62011-04-03 00:25:34 +0200117% helper to send one of the up/down/act/inact management messages + start timer
118send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
119 % generate and send the respective message
120 Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
121 send_sctp_to_peer(LoopDat, Msg),
122 % start T(ack) timer and wait for ASP_UP_ACK
Harald Weltee393ea82011-04-04 16:00:06 +0200123 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte6fc5b292011-04-04 10:38:30 +0200124 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200125 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
126 {next_state, State, LoopDat#m3ua_state{t_ack = Tack}}.
127
128
Harald Welte3bf7cb62011-04-03 00:25:34 +0200129
Harald Welte6fc5b292011-04-04 10:38:30 +0200130handle_event(Event, State, LoopDat) ->
131 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
132 {next_state, State, LoopDat}.
133
134
135
136handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200137 _State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
138 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200139 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
Harald Welteb2d3abf2011-04-04 11:26:11 +0200140 inbound_streams = _InStreams, assoc_id = _AssocId} = SAC,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200141 case SacState of
142 comm_up ->
Harald Weltee393ea82011-04-04 16:00:06 +0200143 % primmitive to the user
144 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200145 LoopDat2 = LoopDat;
146 comm_lost ->
Harald Weltee393ea82011-04-04 16:00:06 +0200147 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200148 LoopDat2 = reconnect_sctp(LoopDat);
149 addr_unreachable ->
150 LoopDat2 = reconnect_sctp(LoopDat)
151 end,
152 inet:setopts(Socket, [{active, once}]),
153 {next_state, asp_down, LoopDat2};
154
Harald Welte6fc5b292011-04-04 10:38:30 +0200155handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200156 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltee393ea82011-04-04 16:00:06 +0200157 % process incoming SCTP data
Harald Welte6fc5b292011-04-04 10:38:30 +0200158 if Socket == LoopDat#m3ua_state.sctp_sock,
159 RemoteIp == LoopDat#m3ua_state.sctp_remote_ip,
160 RemotePort == LoopDat#m3ua_state.sctp_remote_port,
161 3 == Anc#sctp_sndrcvinfo.ppid ->
162 Ret = rx_sctp(Anc, Data, State, LoopDat);
163 true ->
164 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
165 Ret = {next_state, State, LoopDat}
166 end,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200167 inet:setopts(Socket, [{active, once}]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200168 Ret;
Harald Welte3bf7cb62011-04-03 00:25:34 +0200169
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 when is_record(Data, sctp_shutdown_event) ->
172 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
173 inet:setopts(Socket, [{active, once}]),
174 {next_state, asp_down, LoopDat}.
175
176
177
178asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte6fc5b292011-04-04 10:38:30 +0200179 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200180 % M-ASP_UP.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200181 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200182asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
183 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
184
185asp_down(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
186 msg_type = ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200187 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200188 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200189 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200190 {next_state, asp_inactive, LoopDat};
191
192asp_down(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
193 rx_m3ua(M3uaMsg, asp_down, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200194
195
Harald Welte6fc5b292011-04-04 10:38:30 +0200196asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
197 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200198 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200199 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
200 [{?M3UA_IEI_TRAF_MODE_TYPE, <<0,0,0,1>>}]);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200201
202asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
203 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
204
205asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200206 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200207 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200208 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200209
210asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
211 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
212
213asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
214 msg_type = ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200215 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200216 % transition into ASP_ACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200217 % signal this to the user
218 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200219 {next_state, asp_active, LoopDat};
220
221asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
222 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200223 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200224 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200225 % signal this to the user
226 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200227 {next_state, asp_down, LoopDat};
228
229asp_inactive(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
230 rx_m3ua(M3uaMsg, asp_inactive, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200231
232
233
234asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
235 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200236 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200237 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200238 % signal this to the user
239 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200240 {next_state, asp_down, LoopDat};
241
242asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
243 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200244 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200245 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200246 % signal this to the user
247 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200248 {next_state, asp_inactive, LoopDat};
249
250asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200251 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200252 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200253 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200254
255asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
256 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
257
258asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte6fc5b292011-04-04 10:38:30 +0200259 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200260 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200261 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200262
263asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
264 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
265
266asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
267 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200268 % MTP-TRANSFER.req from user app: Send message to remote peer
Harald Welte3bf7cb62011-04-03 00:25:34 +0200269 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
270 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
271 msg_type = ?M3UA_MSGT_XFR_DATA,
272 payload = OptList},
273 send_sctp_to_peer(LoopDat, Msg),
274 {next_state, asp_active, LoopDat};
275asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
276 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200277 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200278 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
Harald Weltecb1c0682011-04-14 21:56:26 +0200279 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,[Mtp3])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200280 {next_state, asp_active, LoopDat};
281asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
282 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
283 timer:cancel(LoopDat#m3ua_state.t_ack),
284 % transition to ASP_INACTIVE
285 {next_state, asp_inactive, LoopDat};
286
Harald Welte6fc5b292011-04-04 10:38:30 +0200287asp_active(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
288 rx_m3ua(M3uaMsg, asp_active, LoopDat).
289
290
Harald Weltee393ea82011-04-04 16:00:06 +0200291
Harald Welteb2d3abf2011-04-04 11:26:11 +0200292rx_sctp(_Anc, Data, State, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200293 M3uaMsg = m3ua_codec:parse_m3ua_msg(Data),
294 gen_fsm:send_event(self(), M3uaMsg),
295 {next_state, State, LoopDat}.
296
297
Harald Weltee393ea82011-04-04 16:00:06 +0200298
Harald Welte6fc5b292011-04-04 10:38:30 +0200299rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
300 msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
Harald Weltee393ea82011-04-04 16:00:06 +0200301 send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200302 {next_state, State, LoopDat};
303
304rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
305 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
306 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte6fc5b292011-04-04 10:38:30 +0200307 send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
308 {next_state, State, LoopDat};
309
Harald Weltee393ea82011-04-04 16:00:06 +0200310rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
311 msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
312 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
313 {next_state, State, LoopDat};
314
315rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
316 msg_type = MsgType, payload = Params}, State, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200317 % transform to classic MTP primitive and send up to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200318 Mtp = map_ssnm_to_mtp_prim(MsgType),
319 send_prim_to_user(LoopDat, Mtp),
320 {next_state, State, LoopDat};
321
Harald Welte6fc5b292011-04-04 10:38:30 +0200322rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
323 io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
324 {next_state, State, LoopDat}.
Harald Weltee393ea82011-04-04 16:00:06 +0200325
Harald Welteb6473702011-04-14 22:06:42 +0200326% Transform the M3UA SSNM messages into classic MTP primitives
Harald Weltee393ea82011-04-04 16:00:06 +0200327map_ssnm_to_mtp_prim(MsgType) ->
328 Mtp = #primitive{subsystem = 'MTP', spec_name = indiciation},
329 case MsgType of
330 ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
331 ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
332 ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
333 ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
334 end.