blob: 3211bfad576644ddb5d1c5f0fc81248eb835541a [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>').
Harald Welteead1ba12011-04-15 10:20:04 +020022-behaviour(gen_fsm).
Harald Welte3bf7cb62011-04-03 00:25:34 +020023
24-include_lib("kernel/include/inet_sctp.hrl").
Harald Weltee393ea82011-04-04 16:00:06 +020025-include("osmo_util.hrl").
Harald Welte3bf7cb62011-04-03 00:25:34 +020026-include("sccp.hrl").
27-include("m3ua.hrl").
28
29-export([start_link/1]).
30
Harald Welteb2d3abf2011-04-04 11:26:11 +020031-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
Harald Welte3bf7cb62011-04-03 00:25:34 +020032
33% FSM states:
34-export([asp_down/2, asp_inactive/2, asp_active/2]).
35
36-define(T_ACK_TIMEOUT, 2*60*100).
37
38% Loop Data
39-record(m3ua_state, {
40 role, % asp | sgp
41 asp_state, % down, inactive, active
42 t_ack,
Harald Weltecb1c0682011-04-14 21:56:26 +020043 user_fun,
44 user_args,
Harald Welte3bf7cb62011-04-03 00:25:34 +020045 sctp_remote_ip,
46 sctp_remote_port,
Harald Welte8a0ab002011-04-03 22:16:12 +020047 sctp_local_port,
Harald Welte3bf7cb62011-04-03 00:25:34 +020048 sctp_sock,
49 sctp_assoc_id
50 }).
51
52start_link(InitOpts) ->
53 gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]).
54
55reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
56 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
Harald Welte8a0ab002011-04-03 22:16:12 +020057 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
Harald Welte3bf7cb62011-04-03 00:25:34 +020058 case gen_sctp:connect(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
59 {sctp_initmsg, InitMsg}]) of
60 {ok, Assoc} ->
Harald Welte9544cab2011-04-04 17:03:23 +020061 send_prim_to_user(L, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +020062 L#m3ua_state{sctp_assoc_id = Assoc#sctp_assoc_change.assoc_id};
63 {error, Error } ->
Harald Welte6fc5b292011-04-04 10:38:30 +020064 io:format("SCTP Error ~p, reconnecting~n", [Error]),
Harald Welte3bf7cb62011-04-03 00:25:34 +020065 reconnect_sctp(L)
66 end.
67
68init(InitOpts) ->
Harald Welte8a0ab002011-04-03 22:16:12 +020069 OpenOptsBase = [{active, once}, {reuseaddr, true}],
70 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
71 case LocalPort of
72 undefined ->
73 OpenOpts = OpenOptsBase;
74 _ ->
75 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
76 end,
77 {ok, SctpSock} = gen_sctp:open(OpenOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020078 LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
Harald Weltecb1c0682011-04-14 21:56:26 +020079 user_fun = proplists:get_value(user_fun, InitOpts),
80 user_args = proplists:get_value(user_args, InitOpts),
Harald Welte3bf7cb62011-04-03 00:25:34 +020081 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Welte8a0ab002011-04-03 22:16:12 +020082 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
83 sctp_local_port = LocalPort},
Harald Welte3bf7cb62011-04-03 00:25:34 +020084 LoopDat2 = reconnect_sctp(LoopDat),
85 {ok, asp_down, LoopDat2}.
86
Harald Welteb2d3abf2011-04-04 11:26:11 +020087terminate(Reason, _State, LoopDat) ->
88 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
89 gen_sctp:close(LoopDat#m3ua_state.sctp_sock).
90
91code_change(_OldVsn, StateName, StateData, _Extra) ->
92 {ok, StateName, StateData}.
93
Harald Welte3bf7cb62011-04-03 00:25:34 +020094% Helper function to send data to the SCTP peer
Harald Weltecb1c0682011-04-14 21:56:26 +020095send_sctp_to_peer(LoopDat, PktData, StreamId) when is_binary(PktData) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +020096 #m3ua_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
Harald Weltecb1c0682011-04-14 21:56:26 +020097 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = 3, stream = StreamId},
98 gen_sctp:send(Sock, SndRcvInfo, PktData).
Harald Welte3bf7cb62011-04-03 00:25:34 +020099
100% same as above, but for un-encoded #m3ua_msg{}
101send_sctp_to_peer(LoopDat, M3uaMsg) when is_record(M3uaMsg, m3ua_msg) ->
102 MsgBin = m3ua_codec:encode_m3ua_msg(M3uaMsg),
Harald Weltecb1c0682011-04-14 21:56:26 +0200103 StreamId = sctp_stream_for_m3ua(M3uaMsg),
104 send_sctp_to_peer(LoopDat, MsgBin, StreamId).
105
106% resolve the Stream ID depending on the m3ua_msg: 0 == management, 1 == trafic
107sctp_stream_for_m3ua(#m3ua_msg{msg_class = Class}) when
108 Class == ?M3UA_MSGC_TRANSFER ->
109 1;
110sctp_stream_for_m3ua(#m3ua_msg{}) ->
111 0.
Harald Welte3bf7cb62011-04-03 00:25:34 +0200112
Harald Weltee393ea82011-04-04 16:00:06 +0200113
114send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, m3ua_state), is_record(Prim, primitive) ->
Harald Weltecb1c0682011-04-14 21:56:26 +0200115 #m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
116 Fun(Prim, Args).
Harald Weltee393ea82011-04-04 16:00:06 +0200117
Harald Welte3bf7cb62011-04-03 00:25:34 +0200118% helper to send one of the up/down/act/inact management messages + start timer
119send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
120 % generate and send the respective message
121 Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
122 send_sctp_to_peer(LoopDat, Msg),
123 % start T(ack) timer and wait for ASP_UP_ACK
Harald Weltee393ea82011-04-04 16:00:06 +0200124 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte6fc5b292011-04-04 10:38:30 +0200125 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200126 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
127 {next_state, State, LoopDat#m3ua_state{t_ack = Tack}}.
128
129
Harald Welte3bf7cb62011-04-03 00:25:34 +0200130
Harald Welte6fc5b292011-04-04 10:38:30 +0200131handle_event(Event, State, LoopDat) ->
132 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
133 {next_state, State, LoopDat}.
134
135
136
137handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
Harald Welte3bf7cb62011-04-03 00:25:34 +0200138 _State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
139 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200140 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
Harald Welteb2d3abf2011-04-04 11:26:11 +0200141 inbound_streams = _InStreams, assoc_id = _AssocId} = SAC,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200142 case SacState of
143 comm_up ->
Harald Weltee393ea82011-04-04 16:00:06 +0200144 % primmitive to the user
145 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_ESTABLISH',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200146 LoopDat2 = LoopDat;
147 comm_lost ->
Harald Weltee393ea82011-04-04 16:00:06 +0200148 send_prim_to_user(LoopDat, osmo_util:make_prim('M','SCTP_RELEASE',indication)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200149 LoopDat2 = reconnect_sctp(LoopDat);
150 addr_unreachable ->
151 LoopDat2 = reconnect_sctp(LoopDat)
152 end,
153 inet:setopts(Socket, [{active, once}]),
154 {next_state, asp_down, LoopDat2};
155
Harald Welte6fc5b292011-04-04 10:38:30 +0200156handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
Harald Welte3bf7cb62011-04-03 00:25:34 +0200157 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
Harald Weltee393ea82011-04-04 16:00:06 +0200158 % process incoming SCTP data
Harald Welte6fc5b292011-04-04 10:38:30 +0200159 if Socket == LoopDat#m3ua_state.sctp_sock,
160 RemoteIp == LoopDat#m3ua_state.sctp_remote_ip,
161 RemotePort == LoopDat#m3ua_state.sctp_remote_port,
162 3 == Anc#sctp_sndrcvinfo.ppid ->
163 Ret = rx_sctp(Anc, Data, State, LoopDat);
164 true ->
165 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
166 Ret = {next_state, State, LoopDat}
167 end,
Harald Welte3bf7cb62011-04-03 00:25:34 +0200168 inet:setopts(Socket, [{active, once}]),
Harald Welte6fc5b292011-04-04 10:38:30 +0200169 Ret;
Harald Welte3bf7cb62011-04-03 00:25:34 +0200170
Harald Welte6fc5b292011-04-04 10:38:30 +0200171handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, _State, LoopDat)
Harald Welte3bf7cb62011-04-03 00:25:34 +0200172 when is_record(Data, sctp_shutdown_event) ->
173 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
174 inet:setopts(Socket, [{active, once}]),
175 {next_state, asp_down, LoopDat}.
176
177
178
179asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte6fc5b292011-04-04 10:38:30 +0200180 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200181 % M-ASP_UP.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200182 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200183asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
184 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
185
186asp_down(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
187 msg_type = ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200188 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200189 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200190 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200191 {next_state, asp_inactive, LoopDat};
192
193asp_down(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
194 rx_m3ua(M3uaMsg, asp_down, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200195
196
Harald Welte6fc5b292011-04-04 10:38:30 +0200197asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
198 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200199 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200200 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
201 [{?M3UA_IEI_TRAF_MODE_TYPE, <<0,0,0,1>>}]);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200202
203asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
204 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
205
206asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200207 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200208 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200209 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200210
211asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
212 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
213
214asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
215 msg_type = ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200216 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200217 % transition into ASP_ACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200218 % signal this to the user
219 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200220 {next_state, asp_active, LoopDat};
221
222asp_inactive(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
223 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200224 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200225 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200226 % signal this to the user
227 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte6fc5b292011-04-04 10:38:30 +0200228 {next_state, asp_down, LoopDat};
229
230asp_inactive(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
231 rx_m3ua(M3uaMsg, asp_inactive, LoopDat).
Harald Welte3bf7cb62011-04-03 00:25:34 +0200232
233
234
235asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPSM,
236 msg_type = ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200237 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200238 % transition into ASP_DOWN
Harald Weltee393ea82011-04-04 16:00:06 +0200239 % signal this to the user
240 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200241 {next_state, asp_down, LoopDat};
242
243asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
244 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200245 timer:cancel(LoopDat#m3ua_state.t_ack),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200246 % transition into ASP_INACTIVE
Harald Weltee393ea82011-04-04 16:00:06 +0200247 % signal this to the user
248 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
Harald Welte3bf7cb62011-04-03 00:25:34 +0200249 {next_state, asp_inactive, LoopDat};
250
251asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte6fc5b292011-04-04 10:38:30 +0200252 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200253 % M-ASP_DOWN.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200254 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200255
256asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
257 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
258
259asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte6fc5b292011-04-04 10:38:30 +0200260 spec_name = request, parameters = _Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200261 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
Harald Welte6fc5b292011-04-04 10:38:30 +0200262 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
Harald Welte3bf7cb62011-04-03 00:25:34 +0200263
264asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
265 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
266
267asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
268 spec_name = request, parameters = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200269 % MTP-TRANSFER.req from user app: Send message to remote peer
Harald Welte3bf7cb62011-04-03 00:25:34 +0200270 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
271 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
272 msg_type = ?M3UA_MSGT_XFR_DATA,
273 payload = OptList},
274 send_sctp_to_peer(LoopDat, Msg),
275 {next_state, asp_active, LoopDat};
276asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
277 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200278 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200279 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
Harald Weltecb1c0682011-04-14 21:56:26 +0200280 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,[Mtp3])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200281 {next_state, asp_active, LoopDat};
282asp_active(#m3ua_msg{msg_class = ?M3UA_MSGC_ASPTM,
283 msg_type = ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
284 timer:cancel(LoopDat#m3ua_state.t_ack),
285 % transition to ASP_INACTIVE
286 {next_state, asp_inactive, LoopDat};
287
Harald Welte6fc5b292011-04-04 10:38:30 +0200288asp_active(M3uaMsg, LoopDat) when is_record(M3uaMsg, m3ua_msg) ->
289 rx_m3ua(M3uaMsg, asp_active, LoopDat).
290
291
Harald Weltee393ea82011-04-04 16:00:06 +0200292
Harald Welteb2d3abf2011-04-04 11:26:11 +0200293rx_sctp(_Anc, Data, State, LoopDat) ->
Harald Welte6fc5b292011-04-04 10:38:30 +0200294 M3uaMsg = m3ua_codec:parse_m3ua_msg(Data),
295 gen_fsm:send_event(self(), M3uaMsg),
296 {next_state, State, LoopDat}.
297
298
Harald Weltee393ea82011-04-04 16:00:06 +0200299
Harald Welte6fc5b292011-04-04 10:38:30 +0200300rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
301 msg_type = ?M3UA_MSGT_MGMT_NTFY}, State, LoopDat) ->
Harald Weltee393ea82011-04-04 16:00:06 +0200302 send_prim_to_user(LoopDat, osmo_util:make_prim('M','NOTIFY',indication,[Msg])),
Harald Welte6fc5b292011-04-04 10:38:30 +0200303 {next_state, State, LoopDat};
304
305rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
306 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
307 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte6fc5b292011-04-04 10:38:30 +0200308 send_sctp_to_peer(LoopDat, Msg#m3ua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
309 {next_state, State, LoopDat};
310
Harald Weltee393ea82011-04-04 16:00:06 +0200311rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_MGMT,
312 msg_type = ?M3UA_MSGT_MGMT_ERR}, State, LoopDat) ->
313 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ERROR',indication,[Msg])),
314 {next_state, State, LoopDat};
315
316rx_m3ua(Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
317 msg_type = MsgType, payload = Params}, State, LoopDat) ->
Harald Welteb6473702011-04-14 22:06:42 +0200318 % transform to classic MTP primitive and send up to the user
Harald Weltee393ea82011-04-04 16:00:06 +0200319 Mtp = map_ssnm_to_mtp_prim(MsgType),
320 send_prim_to_user(LoopDat, Mtp),
321 {next_state, State, LoopDat};
322
Harald Welte6fc5b292011-04-04 10:38:30 +0200323rx_m3ua(Msg = #m3ua_msg{}, State, LoopDat) ->
324 io:format("M3UA Unknown messge ~p in state ~p~n", [Msg, State]),
325 {next_state, State, LoopDat}.
Harald Weltee393ea82011-04-04 16:00:06 +0200326
Harald Welteb6473702011-04-14 22:06:42 +0200327% Transform the M3UA SSNM messages into classic MTP primitives
Harald Weltee393ea82011-04-04 16:00:06 +0200328map_ssnm_to_mtp_prim(MsgType) ->
329 Mtp = #primitive{subsystem = 'MTP', spec_name = indiciation},
330 case MsgType of
331 ?M3UA_MSGT_SSNM_DUNA -> Mtp#primitive{gen_name = 'PAUSE'};
332 ?M3UA_MSGT_SSNM_DAVA -> Mtp#primitive{gen_name = 'RESUME'};
333 ?M3UA_MSGT_SSNM_SCON -> Mtp#primitive{gen_name = 'STATUS'};
334 ?M3UA_MSGT_SSNM_DUPU -> Mtp#primitive{gen_name = 'STATUS'}
335 end.