blob: 95075f0350315f7d117150c04776ff37e861bf5c [file] [log] [blame]
Harald Welte475ccdb2012-01-17 10:11:58 +01001% SCCP M3UA / SUA ASP gsn_fsm according to RFC3868 4.3.1
2
3% (C) 2011-2012 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 Welte475ccdb2012-01-17 10:11:58 +010033
34-module(xua_asp_fsm).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(gen_fsm).
37
38-include("osmo_util.hrl").
39-include("m3ua.hrl").
40
41% gen_fsm exports
Harald Welte312a1eb2012-05-09 00:02:59 +020042-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3,
43 handle_sync_event/4]).
Harald Welte475ccdb2012-01-17 10:11:58 +010044
45% states in this FSM
46-export([asp_down/2, asp_inactive/2, asp_active/2]).
47
48% helper functions exporte to callback modules
49-export([send_sctp_to_peer/2, send_prim_to_user/2]).
50
Harald Welte312a1eb2012-05-09 00:02:59 +020051% global exports
Harald Welte0d8af6b2013-07-27 15:02:17 +080052-export([get_state/1, start_link/7]).
Harald Welte312a1eb2012-05-09 00:02:59 +020053
Harald Welte475ccdb2012-01-17 10:11:58 +010054-export([behaviour_info/1]).
55
56behaviour_info(callbacks) ->
57 [{gen_xua_msg, 3}, {asp_down, 3}, {asp_inactive, 3}, {asp_active, 3}].
58
59% Timeouts in milliseconds
60-define(T_ACK_TIMEOUT, 2*60*100).
61
62-record(asp_state, {
63 module,
Harald Welte0d8af6b2013-07-27 15:02:17 +080064 role, % asp, sg
Harald Welte475ccdb2012-01-17 10:11:58 +010065 t_ack,
66 ext_state,
67 user_fun,
68 user_args,
Harald Welteeb618852012-05-08 23:50:04 +020069 as_pid,
Harald Welte475ccdb2012-01-17 10:11:58 +010070 sctp_pid
71 }).
72
Harald Welte0d8af6b2013-07-27 15:02:17 +080073start_link(AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role) ->
74 gen_fsm:start_link(?MODULE, [AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role], [{debug, [trace]}]).
Harald Weltedd35d2c2012-05-09 00:10:39 +020075
Harald Welte475ccdb2012-01-17 10:11:58 +010076%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
77% gen_fsm callbacks
78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79
Harald Welte0d8af6b2013-07-27 15:02:17 +080080init([AsPid, Module, ModuleArgs, UserFun, UserArgs, SctpPid, Role]) ->
Harald Welte475ccdb2012-01-17 10:11:58 +010081 {ok, ExtState} = Module:init(ModuleArgs),
82 AspState = #asp_state{module = Module,
83 user_fun = UserFun,
84 user_args = UserArgs,
85 ext_state = ExtState,
Harald Welteeb618852012-05-08 23:50:04 +020086 as_pid = AsPid,
Harald Welte475ccdb2012-01-17 10:11:58 +010087 sctp_pid = SctpPid,
Harald Welte0d8af6b2013-07-27 15:02:17 +080088 role = Role},
Harald Welte475ccdb2012-01-17 10:11:58 +010089 {ok, asp_down, AspState}.
90
91terminate(Reason, State, _LoopDat) ->
92 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
93 [?MODULE, State, Reason]),
94 ok.
95
96code_change(_OldVsn, StateName, LoopDat, _Extra) ->
97 {ok, StateName, LoopDat}.
98
99handle_event(Event, State, LoopDat) ->
100 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
101 {next_state, State, LoopDat}.
102
103
104handle_info(Info, State, LoopDat) ->
105 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
106 {next_state, State, LoopDat}.
107
Harald Welte312a1eb2012-05-09 00:02:59 +0200108handle_sync_event(get_state, _From, StateName, LoopDat) ->
109 {reply, state2aspas(StateName), StateName, LoopDat}.
110
111%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
112% exports
113%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
114
115get_state(Pid) ->
116 gen_fsm:sync_send_all_state_event(Pid, get_state).
Harald Welte475ccdb2012-01-17 10:11:58 +0100117
118%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
119% STATE "asp_down"
120%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
121
122asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
Harald Welte0d8af6b2013-07-27 15:02:17 +0800123 spec_name = request, parameters = _Params},
124 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100125 % M-ASP_UP.req from user, generate message and send to remote peer
126 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
127asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
128 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
129
Harald Welte0d8af6b2013-07-27 15:02:17 +0800130asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK},
131 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100132 timer:cancel(LoopDat#asp_state.t_ack),
133 % transition into ASP_INACTIVE
134 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
Harald Welteeb618852012-05-08 23:50:04 +0200135 next_state(asp_inactive, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100136
Harald Welte0d8af6b2013-07-27 15:02:17 +0800137asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP},
138 LoopDat = #asp_state{role=sg}) ->
139 % transition into ASP_INACTIVE
Harald Weltea5409502013-07-27 15:08:29 +0800140 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',indication)),
Harald Welte0d8af6b2013-07-27 15:02:17 +0800141 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK, []);
142
Harald Welte475ccdb2012-01-17 10:11:58 +0100143asp_down(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
Harald Welteeb618852012-05-08 23:50:04 +0200144 {State, LDnew} = Module:asp_down(WhateverElse, ExtState, LoopDat),
145 next_state(State, LDnew).
Harald Welte475ccdb2012-01-17 10:11:58 +0100146
147
148%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
149% STATE "asp_inactive"
150%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
151
152asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
Harald Welte0d8af6b2013-07-27 15:02:17 +0800153 spec_name = request, parameters = Params},
154 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100155 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
156 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
157 Params);
158
159asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
160 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
161
162asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte0d8af6b2013-07-27 15:02:17 +0800163 spec_name = request, parameters = _Params},
164 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100165 % M-ASP_DOWN.req from user, generate message and send to remote peer
166 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
167
168asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
169 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
170
Harald Welte0d8af6b2013-07-27 15:02:17 +0800171asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK},
172 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100173 timer:cancel(LoopDat#asp_state.t_ack),
174 % transition into ASP_ACTIVE
175 % signal this to the user
176 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
Harald Welteeb618852012-05-08 23:50:04 +0200177 next_state(asp_active, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100178
Harald Welte0d8af6b2013-07-27 15:02:17 +0800179asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK},
180 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100181 timer:cancel(LoopDat#asp_state.t_ack),
182 % transition into ASP_DOWN
183 % signal this to the user
184 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welteeb618852012-05-08 23:50:04 +0200185 next_state(asp_down, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100186
Harald Welte0d8af6b2013-07-27 15:02:17 +0800187
188asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC},
189 LoopDat = #asp_state{role=sg}) ->
190 % transition into ASP_ACTIVE
191 % signal this to the user
192 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',indication)),
193 send_msg(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK, []);
194
195asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN},
196 LoopDat = #asp_state{role=asp}) ->
197 % transition into ASP_DOWN
198 % signal this to the user
199 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',indication)),
200 send_msg(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK, []);
201
202
Harald Welte475ccdb2012-01-17 10:11:58 +0100203asp_inactive(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
Harald Welteeb618852012-05-08 23:50:04 +0200204 {State, LDnew} = Module:asp_inactive(WhateverElse, ExtState, LoopDat),
205 next_state(State, LDnew).
Harald Welte475ccdb2012-01-17 10:11:58 +0100206
207
208%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
209% STATE "asp_active"
210%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
211
Harald Welte0d8af6b2013-07-27 15:02:17 +0800212asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK},
213 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100214 timer:cancel(LoopDat#asp_state.t_ack),
215 % transition into ASP_DOWN
216 % signal this to the user
217 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
Harald Welteeb618852012-05-08 23:50:04 +0200218 next_state(asp_down, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100219
Harald Welte0d8af6b2013-07-27 15:02:17 +0800220asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK},
221 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100222 timer:cancel(LoopDat#asp_state.t_ack),
223 % transition into ASP_INACTIVE
224 % signal this to the user
225 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
Harald Welteeb618852012-05-08 23:50:04 +0200226 next_state(asp_inactive, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100227
228asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
Harald Welte0d8af6b2013-07-27 15:02:17 +0800229 spec_name = request, parameters = _Params},
230 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100231 % M-ASP_DOWN.req from user, generate message and send to remote peer
232 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
233
234asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
235 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
236
237asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
Harald Welte0d8af6b2013-07-27 15:02:17 +0800238 spec_name = request, parameters = _Params},
239 LoopDat = #asp_state{role=asp}) ->
Harald Welte475ccdb2012-01-17 10:11:58 +0100240 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
241 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
242
243asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
244 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
245
Harald Welte0d8af6b2013-07-27 15:02:17 +0800246asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA},
247 LoopDat = #asp_state{role=sg}) ->
248 % transition into ASP_INACTIVE
249 % signal this to user
250 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',indication)),
251 send_msg(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK, []);
252
253asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN},
254 LoopDat = #asp_state{role=sg}) ->
255 % transition into ASP_INACTIVE
256 % signal this to user
257 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',indication)),
258 send_msg(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK, []);
259
260
Harald Welte475ccdb2012-01-17 10:11:58 +0100261asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
262 spec_name = request, parameters = Params}, LoopDat) ->
263 % MTP-TRANSFER.req from user app: Send message to remote peer
264 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
265 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
266 msg_type = ?M3UA_MSGT_XFR_DATA,
267 payload = OptList},
268 send_sctp_to_peer(LoopDat, Msg),
Harald Welteeb618852012-05-08 23:50:04 +0200269 next_state(asp_active, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100270asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
271 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
272 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
273 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
274 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,Mtp3)),
Harald Welteeb618852012-05-08 23:50:04 +0200275 next_state(asp_active, LoopDat);
Harald Welte475ccdb2012-01-17 10:11:58 +0100276
277asp_active(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
Harald Welteeb618852012-05-08 23:50:04 +0200278 {State, LDnew} = Module:asp_active(WhateverElse, ExtState, LoopDat),
279 next_state(State, LDnew).
Harald Welte475ccdb2012-01-17 10:11:58 +0100280
281
282%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
283% helper functions
284%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
285
286% helper to send one of the up/down/act/inact management messages + start timer
287send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
288 Module = LoopDat#asp_state.module,
289 % generate and send the respective message
290 %Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
291 Msg = Module:gen_xua_msg(MsgClass, MsgType, Params),
292 send_sctp_to_peer(LoopDat, Msg),
293 % start T(ack) timer and wait for ASP_UP_ACK
294 timer:cancel(LoopDat#asp_state.t_ack),
295 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
296 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
Harald Welteeb618852012-05-08 23:50:04 +0200297 next_state(State, LoopDat#asp_state{t_ack = Tack}).
Harald Welte475ccdb2012-01-17 10:11:58 +0100298
Harald Welte0d8af6b2013-07-27 15:02:17 +0800299send_msg(LoopDat, State, MsgClass, MsgType, Params) ->
300 Module = LoopDat#asp_state.module,
301 % generate and send the respective message
302 Msg = Module:gen_xua_msg(MsgClass, MsgType, Params),
303 send_sctp_to_peer(LoopDat, Msg),
304 next_state(State, LoopDat).
Harald Welte475ccdb2012-01-17 10:11:58 +0100305
306send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, asp_state),
307 is_record(Prim, primitive) ->
308 #asp_state{user_fun = Fun, user_args = Args} = LoopDat,
309 Fun(Prim, Args).
310
Harald Welteeb618852012-05-08 23:50:04 +0200311state2aspas(asp_down) -> 'ASP_DOWN';
312state2aspas(asp_inactive) -> 'ASP_INACTIVE';
313state2aspas(asp_active) -> 'ASP_ACTIVE'.
314
315% propagate an ASP state transition as ASPAS primitive to AS
316next_state(State, LoopDat = #asp_state{as_pid = AsPid}) ->
317 Prim = osmo_util:make_prim('ASPAS', state2aspas(State), indication),
Harald Welte43ceb092013-07-27 14:12:58 +0800318 case AsPid of
319 undefined ->
320 ok;
321 _ ->
322 gen_fsm:send_event(AsPid, Prim)
323 end,
Harald Welteeb618852012-05-08 23:50:04 +0200324 {next_state, State, LoopDat}.
Harald Welte475ccdb2012-01-17 10:11:58 +0100325
326% Helper function to send data to the SCTP peer
327send_sctp_to_peer(LoopDat, Msg) ->
328 Prim = osmo_util:make_prim('MTP','TRANSFER',request, Msg),
329 gen_fsm:send_event(LoopDat#asp_state.sctp_pid, Prim).