blob: 1e9fc210e50350bffcefe762acc7fdcd3687e202 [file] [log] [blame]
Harald Welte26bdef22012-01-16 22:22:17 +01001% SCTP wrapper behavior, used by M2PA/M2UA/M3UA/SUA
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 Welte26bdef22012-01-16 22:22:17 +010033
34-module(sctp_core).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(gen_fsm).
37
38-include_lib("kernel/include/inet_sctp.hrl").
39-include("osmo_util.hrl").
40
41-export([start_link/1]).
42
43-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
44
45-export([behaviour_info/1]).
46
47% FSM states:
48-export([idle/2, associating/2, established/2]).
49
50behaviour_info(callbacks) ->
Harald Welte91b79652012-01-17 10:12:34 +010051 gen_fsm:behaviour_info(callbacks) ++
52 [{rx_sctp, 4}, {mtp_xfer, 2}, {state_change, 2}, {prim_up, 3}];
Harald Welte26bdef22012-01-16 22:22:17 +010053behaviour_info(Other) ->
54 gen_fsm:behaviour_info(Other).
55
56% Loop Data
57-record(sctp_state, {
58 role, % passive | active
59 state, % idle | associating | established
60 user_pid,
61 sctp_remote_ip,
62 sctp_remote_port,
Harald Welte26bdef22012-01-16 22:22:17 +010063 sctp_sock,
64 sctp_assoc_id,
65 module, % callback module
66 ext_state % state of the callback module
67 }).
68
69start_link(InitOpts) ->
Harald Weltedd039952013-07-27 14:13:37 +080070 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
71 Name = list_to_atom("sctp_core_" ++ integer_to_list(LocalPort)),
72 gen_fsm:start_link({local, Name}, ?MODULE, InitOpts, [{debug, [trace]}]).
Harald Welte26bdef22012-01-16 22:22:17 +010073
74reconnect_sctp(L = #sctp_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
75 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
76 timer:sleep(1*1000),
77 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
78 case gen_sctp:connect_init(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
79 {sctp_initmsg, InitMsg}]) of
80 ok ->
81 ok;
82 {error, Error } ->
83 io:format("SCTP Error ~p, reconnecting~n", [Error]),
84 reconnect_sctp(L)
85 end.
86
Harald Weltee1260682013-09-08 22:00:41 +020087build_openopt({sctp_local_port, Port}) ->
88 {port, Port};
Harald Welte48c07f02013-09-08 22:22:01 +020089build_openopt({sctp_local_ip, undefined}) ->
90 [];
Harald Weltee1260682013-09-08 22:00:41 +020091build_openopt({sctp_local_ip, Ip}) ->
92 {ip, Ip};
93build_openopt(_) ->
94 [].
Harald Welte48c07f02013-09-08 22:22:01 +020095build_openopts(PropList) ->
96 [{active, once}, {reuseaddr, true}] ++
97 lists:flatten(lists:map(fun build_openopt/1, PropList)).
Harald Weltee1260682013-09-08 22:00:41 +020098
Harald Welte26bdef22012-01-16 22:22:17 +010099init(InitOpts) ->
Harald Welte26bdef22012-01-16 22:22:17 +0100100 Module = proplists:get_value(module, InitOpts),
101 ModuleArgs = proplists:get_value(module_args, InitOpts),
Harald Welte26bdef22012-01-16 22:22:17 +0100102 Role = proplists:get_value(sctp_role, InitOpts),
Harald Welte48c07f02013-09-08 22:22:01 +0200103 {ok, SctpSock} = gen_sctp:open(build_openopts(InitOpts)),
Harald Welte26bdef22012-01-16 22:22:17 +0100104 case Module:init(ModuleArgs) of
105 {ok, ExtState} ->
106 LoopDat = #sctp_state{role = Role, sctp_sock = SctpSock,
107 user_pid = proplists:get_value(user_pid, InitOpts),
108 ext_state = ExtState, module = Module,
109 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
Harald Weltee1260682013-09-08 22:00:41 +0200110 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts)},
Harald Welte26bdef22012-01-16 22:22:17 +0100111 case Role of
112 active ->
113 gen_fsm:send_event(self(), osmo_util:make_prim('M','SCTP_ESTABLISH',request));
114 _ ->
Harald Weltedd039952013-07-27 14:13:37 +0800115 ok = gen_sctp:listen(SctpSock, true)
Harald Welte26bdef22012-01-16 22:22:17 +0100116 end,
117 {ok, idle, LoopDat};
118 Default ->
119 {error, {module_returned, Default}}
120 end.
121
122terminate(Reason, State, LoopDat) ->
123 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
124 Module = LoopDat#sctp_state.module,
125 gen_sctp:close(LoopDat#sctp_state.sctp_sock),
126 Module:terminate(Reason, State, LoopDat#sctp_state.ext_state).
127
128code_change(OldVsn, StateName, LoopDat, Extra) ->
129 Module = LoopDat#sctp_state.module,
130 case Module:code_change(OldVsn, StateName, LoopDat#sctp_state.ext_state, Extra) of
131 {ok, ExtState} ->
132 {ok, StateName, LoopDat#sctp_state{ext_state = ExtState}};
133 Other ->
134 Other
135 end.
136
137% Helper function to send data to the SCTP peer
138send_sctp_to_peer(LoopDat, PktData, StreamId, Ppid) when is_binary(PktData) ->
139 #sctp_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
140 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = Ppid, stream = StreamId},
141 gen_sctp:send(Sock, SndRcvInfo, PktData).
142
143send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, sctp_state), is_record(Prim, primitive) ->
Harald Welte26bdef22012-01-16 22:22:17 +0100144 UserPid = LoopDat#sctp_state.user_pid,
145 UserPid ! Prim.
146
Harald Welte91b79652012-01-17 10:12:34 +0100147prim_up_to_callback(Prim, State, LoopDat) ->
148 Module = LoopDat#sctp_state.module,
149 case Module:prim_up(Prim, State, LoopDat#sctp_state.ext_state) of
150 {ok, Prim, ExtNew} ->
151 send_prim_to_user(LoopDat, Prim);
152 {ignore, ExtNew} ->
153 ok
154 end,
155 LoopDat#sctp_state{ext_state = ExtNew}.
156
Harald Welte26bdef22012-01-16 22:22:17 +0100157
158handle_event(Event, State, LoopDat) ->
159 Module = LoopDat#sctp_state.module,
160 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
161 case Module:handle_event(Event, State, LoopDat#sctp_state.ext_state) of
162 {next_state, State, ExtState} ->
163 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
164 end.
165
166
167handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
168 State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
169 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
170 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
171 inbound_streams = _InStreams, assoc_id = AssocId} = SAC,
172 if
173 SacState == comm_up;
174 SacState == restart ->
175 case State of
176 associating ->
177 NewState = established,
178 Spec = confirm;
Harald Weltedd039952013-07-27 14:13:37 +0800179 idle ->
180 NewState = established,
181 Spec = indication;
Harald Welte26bdef22012-01-16 22:22:17 +0100182 _ ->
183 NewState = State,
184 Spec = indication
185 end,
186 % primitive to the user
Harald Welte91b79652012-01-17 10:12:34 +0100187 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_ESTABLISH',Spec),
188 State, LoopDat);
Harald Welte26bdef22012-01-16 22:22:17 +0100189 SacState == comm_lost ->
190 case State of
191 releasing ->
192 Spec = confirm;
193 _ ->
194 Spec = indication
195 end,
Harald Welte91b79652012-01-17 10:12:34 +0100196 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_RELEASE',Spec),
197 State, LoopDat),
Harald Welte26bdef22012-01-16 22:22:17 +0100198 case LoopDat#sctp_state.role of
199 active ->
200 NewState = associating,
Harald Welte91b79652012-01-17 10:12:34 +0100201 reconnect_sctp(LoopDat2);
Harald Welte26bdef22012-01-16 22:22:17 +0100202 _ ->
203 NewState = idle
204 end;
Harald Welte23a45c12012-01-19 23:09:17 +0100205 SacState == addr_unreachable;
206 SacState == cant_assoc ->
Harald Welte26bdef22012-01-16 22:22:17 +0100207 case LoopDat#sctp_state.role of
208 active ->
209 NewState = associating,
210 reconnect_sctp(LoopDat);
211 _ ->
212 NewState = idle
Harald Welte91b79652012-01-17 10:12:34 +0100213 end,
Harald Weltee1260682013-09-08 22:00:41 +0200214 LoopDat2 = LoopDat;
215 SacState == shutdown_comp ->
216 % we already started reconnect in shutdown_event
217 NewState = State,
Harald Welte91b79652012-01-17 10:12:34 +0100218 LoopDat2 = LoopDat
Harald Welte26bdef22012-01-16 22:22:17 +0100219 end,
220 inet:setopts(Socket, [{active, once}]),
Harald Welte91b79652012-01-17 10:12:34 +0100221 next_state(State, NewState, LoopDat2#sctp_state{sctp_assoc_id = AssocId});
Harald Welte26bdef22012-01-16 22:22:17 +0100222
223handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
224 Module = LoopDat#sctp_state.module,
225 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
226 % process incoming SCTP data
227 if Socket == LoopDat#sctp_state.sctp_sock,
228 RemoteIp == LoopDat#sctp_state.sctp_remote_ip,
229 RemotePort == LoopDat#sctp_state.sctp_remote_port ->
230 Ret = Module:rx_sctp(Anc, Data, State, LoopDat#sctp_state.ext_state),
231 case Ret of
232 {ok, Prim, ExtState} ->
233 send_prim_to_user(LoopDat, Prim);
234 {ignore, ExtState} ->
235 ok
236 end;
237 true ->
238 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
239 ExtState = LoopDat#sctp_state.ext_state
240 end,
241 inet:setopts(Socket, [{active, once}]),
242 next_state(State, State, LoopDat#sctp_state{ext_state = ExtState});
243
244handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, State, LoopDat)
245 when is_record(Data, sctp_shutdown_event) ->
246 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
247 % FIXME: send SCTP_RELEASE.ind ?
248 inet:setopts(Socket, [{active, once}]),
249 case LoopDat#sctp_state.role of
250 active ->
251 reconnect_sctp(LoopDat);
252 _ ->
253 ok
254 end,
255 next_state(State, associating, LoopDat);
256
257handle_info(Info, State, LoopDat) ->
258 Module = LoopDat#sctp_state.module,
259 case Module:handle_info(Info, State, LoopDat#sctp_state.ext_state) of
260 {next_state, State, ExtState} ->
261 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
262 end.
263
264
265idle(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100266 % M-SCTP_ESTABLISH.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100267 case LoopDat#sctp_state.role of
268 active ->
269 reconnect_sctp(LoopDat);
270 _ ->
271 ok
272 end,
Harald Welte91b79652012-01-17 10:12:34 +0100273 next_state(idle, associating, LoopDat);
274idle(Prim, LoopDat) when is_record(Prim, primitive) ->
275 LoopDat2 = prim_up_to_callback(Prim, idle, LoopDat),
276 next_state(idle, idle, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100277
278
279
280associating(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
281 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100282 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100283 % directly send RELEASE.conf ?!?
Harald Welte91b79652012-01-17 10:12:34 +0100284 next_state(associating, idle, LoopDat);
285associating(Prim, LoopDat) when is_record(Prim, primitive) ->
286 LoopDat2 = prim_up_to_callback(Prim, associating, LoopDat),
287 next_state(associating, associating, LoopDat2).
288
Harald Welte26bdef22012-01-16 22:22:17 +0100289
290
291established(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
292 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100293 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100294 next_state(established, releasing, LoopDat);
295established(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
296 spec_name = request, parameters = Params}, LoopDat) ->
297 % MTP-TRANSFER.req from user app; Send message to remote peer
298 Module = LoopDat#sctp_state.module,
299 ExtState = Module:mtp_xfer(Params, LoopDat#sctp_state.ext_state),
300 next_state(established, established, LoopDat#sctp_state{ext_state = ExtState});
301established(#primitive{subsystem = 'SCTP', gen_name = 'TRANSFER',
302 spec_name = request, parameters = {Stream, Ppid, Data}}, LoopDat) ->
303 io:format("SCTP-TRANSFER.req~n",[]),
304 % somebody (typically callback module) requests us to send SCTP data
305 send_sctp_to_peer(LoopDat, Data, Stream, Ppid),
Harald Welte91b79652012-01-17 10:12:34 +0100306 next_state(established, established, LoopDat);
307established(Prim, LoopDat) when is_record(Prim, primitive) ->
308 LoopDat2 = prim_up_to_callback(Prim, established, LoopDat),
309 next_state(established, established, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100310
311next_state(State, NewState, LoopDat) when is_record(LoopDat, sctp_state) ->
312 Module = LoopDat#sctp_state.module,
313 case NewState of
314 State ->
315 {next_state, NewState, LoopDat};
316 _ ->
317 ExtState = Module:state_change(State, NewState, LoopDat#sctp_state.ext_state),
318 {next_state, NewState, LoopDat#sctp_state{ext_state = ExtState}}
319 end.