blob: 291746bdc19f13061b9b856dbe813ffb2a655428 [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,
63 sctp_local_port,
64 sctp_sock,
65 sctp_assoc_id,
66 module, % callback module
67 ext_state % state of the callback module
68 }).
69
70start_link(InitOpts) ->
Harald Weltedd039952013-07-27 14:13:37 +080071 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
72 Name = list_to_atom("sctp_core_" ++ integer_to_list(LocalPort)),
73 gen_fsm:start_link({local, Name}, ?MODULE, InitOpts, [{debug, [trace]}]).
Harald Welte26bdef22012-01-16 22:22:17 +010074
75reconnect_sctp(L = #sctp_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
76 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
77 timer:sleep(1*1000),
78 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
79 case gen_sctp:connect_init(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
80 {sctp_initmsg, InitMsg}]) of
81 ok ->
82 ok;
83 {error, Error } ->
84 io:format("SCTP Error ~p, reconnecting~n", [Error]),
85 reconnect_sctp(L)
86 end.
87
88init(InitOpts) ->
89 OpenOptsBase = [{active, once}, {reuseaddr, true}],
90 Module = proplists:get_value(module, InitOpts),
91 ModuleArgs = proplists:get_value(module_args, InitOpts),
92 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
93 Role = proplists:get_value(sctp_role, InitOpts),
94 case LocalPort of
95 undefined ->
96 OpenOpts = OpenOptsBase;
97 _ ->
98 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
99 end,
100 {ok, SctpSock} = gen_sctp:open(OpenOpts),
101 case Module:init(ModuleArgs) of
102 {ok, ExtState} ->
103 LoopDat = #sctp_state{role = Role, sctp_sock = SctpSock,
104 user_pid = proplists:get_value(user_pid, InitOpts),
105 ext_state = ExtState, module = Module,
106 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
107 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
108 sctp_local_port = LocalPort},
109 case Role of
110 active ->
111 gen_fsm:send_event(self(), osmo_util:make_prim('M','SCTP_ESTABLISH',request));
112 _ ->
Harald Weltedd039952013-07-27 14:13:37 +0800113 ok = gen_sctp:listen(SctpSock, true)
Harald Welte26bdef22012-01-16 22:22:17 +0100114 end,
115 {ok, idle, LoopDat};
116 Default ->
117 {error, {module_returned, Default}}
118 end.
119
120terminate(Reason, State, LoopDat) ->
121 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
122 Module = LoopDat#sctp_state.module,
123 gen_sctp:close(LoopDat#sctp_state.sctp_sock),
124 Module:terminate(Reason, State, LoopDat#sctp_state.ext_state).
125
126code_change(OldVsn, StateName, LoopDat, Extra) ->
127 Module = LoopDat#sctp_state.module,
128 case Module:code_change(OldVsn, StateName, LoopDat#sctp_state.ext_state, Extra) of
129 {ok, ExtState} ->
130 {ok, StateName, LoopDat#sctp_state{ext_state = ExtState}};
131 Other ->
132 Other
133 end.
134
135% Helper function to send data to the SCTP peer
136send_sctp_to_peer(LoopDat, PktData, StreamId, Ppid) when is_binary(PktData) ->
137 #sctp_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
138 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = Ppid, stream = StreamId},
139 gen_sctp:send(Sock, SndRcvInfo, PktData).
140
141send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, sctp_state), is_record(Prim, primitive) ->
Harald Welte26bdef22012-01-16 22:22:17 +0100142 UserPid = LoopDat#sctp_state.user_pid,
143 UserPid ! Prim.
144
Harald Welte91b79652012-01-17 10:12:34 +0100145prim_up_to_callback(Prim, State, LoopDat) ->
146 Module = LoopDat#sctp_state.module,
147 case Module:prim_up(Prim, State, LoopDat#sctp_state.ext_state) of
148 {ok, Prim, ExtNew} ->
149 send_prim_to_user(LoopDat, Prim);
150 {ignore, ExtNew} ->
151 ok
152 end,
153 LoopDat#sctp_state{ext_state = ExtNew}.
154
Harald Welte26bdef22012-01-16 22:22:17 +0100155
156handle_event(Event, State, LoopDat) ->
157 Module = LoopDat#sctp_state.module,
158 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
159 case Module:handle_event(Event, State, LoopDat#sctp_state.ext_state) of
160 {next_state, State, ExtState} ->
161 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
162 end.
163
164
165handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
166 State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
167 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
168 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
169 inbound_streams = _InStreams, assoc_id = AssocId} = SAC,
170 if
171 SacState == comm_up;
172 SacState == restart ->
173 case State of
174 associating ->
175 NewState = established,
176 Spec = confirm;
Harald Weltedd039952013-07-27 14:13:37 +0800177 idle ->
178 NewState = established,
179 Spec = indication;
Harald Welte26bdef22012-01-16 22:22:17 +0100180 _ ->
181 NewState = State,
182 Spec = indication
183 end,
184 % primitive to the user
Harald Welte91b79652012-01-17 10:12:34 +0100185 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_ESTABLISH',Spec),
186 State, LoopDat);
Harald Welte26bdef22012-01-16 22:22:17 +0100187 SacState == comm_lost ->
188 case State of
189 releasing ->
190 Spec = confirm;
191 _ ->
192 Spec = indication
193 end,
Harald Welte91b79652012-01-17 10:12:34 +0100194 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_RELEASE',Spec),
195 State, LoopDat),
Harald Welte26bdef22012-01-16 22:22:17 +0100196 case LoopDat#sctp_state.role of
197 active ->
198 NewState = associating,
Harald Welte91b79652012-01-17 10:12:34 +0100199 reconnect_sctp(LoopDat2);
Harald Welte26bdef22012-01-16 22:22:17 +0100200 _ ->
201 NewState = idle
202 end;
Harald Welte23a45c12012-01-19 23:09:17 +0100203 SacState == addr_unreachable;
Harald Welte7266d7e2013-07-27 15:01:22 +0800204 SacState == shutdown_comp;
Harald Welte23a45c12012-01-19 23:09:17 +0100205 SacState == cant_assoc ->
Harald Welte26bdef22012-01-16 22:22:17 +0100206 case LoopDat#sctp_state.role of
207 active ->
208 NewState = associating,
209 reconnect_sctp(LoopDat);
210 _ ->
211 NewState = idle
Harald Welte91b79652012-01-17 10:12:34 +0100212 end,
213 LoopDat2 = LoopDat
Harald Welte26bdef22012-01-16 22:22:17 +0100214 end,
215 inet:setopts(Socket, [{active, once}]),
Harald Welte91b79652012-01-17 10:12:34 +0100216 next_state(State, NewState, LoopDat2#sctp_state{sctp_assoc_id = AssocId});
Harald Welte26bdef22012-01-16 22:22:17 +0100217
218handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
219 Module = LoopDat#sctp_state.module,
220 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
221 % process incoming SCTP data
222 if Socket == LoopDat#sctp_state.sctp_sock,
223 RemoteIp == LoopDat#sctp_state.sctp_remote_ip,
224 RemotePort == LoopDat#sctp_state.sctp_remote_port ->
225 Ret = Module:rx_sctp(Anc, Data, State, LoopDat#sctp_state.ext_state),
226 case Ret of
227 {ok, Prim, ExtState} ->
228 send_prim_to_user(LoopDat, Prim);
229 {ignore, ExtState} ->
230 ok
231 end;
232 true ->
233 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
234 ExtState = LoopDat#sctp_state.ext_state
235 end,
236 inet:setopts(Socket, [{active, once}]),
237 next_state(State, State, LoopDat#sctp_state{ext_state = ExtState});
238
239handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, State, LoopDat)
240 when is_record(Data, sctp_shutdown_event) ->
241 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
242 % FIXME: send SCTP_RELEASE.ind ?
243 inet:setopts(Socket, [{active, once}]),
244 case LoopDat#sctp_state.role of
245 active ->
246 reconnect_sctp(LoopDat);
247 _ ->
248 ok
249 end,
250 next_state(State, associating, LoopDat);
251
252handle_info(Info, State, LoopDat) ->
253 Module = LoopDat#sctp_state.module,
254 case Module:handle_info(Info, State, LoopDat#sctp_state.ext_state) of
255 {next_state, State, ExtState} ->
256 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
257 end.
258
259
260idle(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100261 % M-SCTP_ESTABLISH.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100262 case LoopDat#sctp_state.role of
263 active ->
264 reconnect_sctp(LoopDat);
265 _ ->
266 ok
267 end,
Harald Welte91b79652012-01-17 10:12:34 +0100268 next_state(idle, associating, LoopDat);
269idle(Prim, LoopDat) when is_record(Prim, primitive) ->
270 LoopDat2 = prim_up_to_callback(Prim, idle, LoopDat),
271 next_state(idle, idle, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100272
273
274
275associating(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
276 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100277 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100278 % directly send RELEASE.conf ?!?
Harald Welte91b79652012-01-17 10:12:34 +0100279 next_state(associating, idle, LoopDat);
280associating(Prim, LoopDat) when is_record(Prim, primitive) ->
281 LoopDat2 = prim_up_to_callback(Prim, associating, LoopDat),
282 next_state(associating, associating, LoopDat2).
283
Harald Welte26bdef22012-01-16 22:22:17 +0100284
285
286established(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
287 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100288 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100289 next_state(established, releasing, LoopDat);
290established(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
291 spec_name = request, parameters = Params}, LoopDat) ->
292 % MTP-TRANSFER.req from user app; Send message to remote peer
293 Module = LoopDat#sctp_state.module,
294 ExtState = Module:mtp_xfer(Params, LoopDat#sctp_state.ext_state),
295 next_state(established, established, LoopDat#sctp_state{ext_state = ExtState});
296established(#primitive{subsystem = 'SCTP', gen_name = 'TRANSFER',
297 spec_name = request, parameters = {Stream, Ppid, Data}}, LoopDat) ->
298 io:format("SCTP-TRANSFER.req~n",[]),
299 % somebody (typically callback module) requests us to send SCTP data
300 send_sctp_to_peer(LoopDat, Data, Stream, Ppid),
Harald Welte91b79652012-01-17 10:12:34 +0100301 next_state(established, established, LoopDat);
302established(Prim, LoopDat) when is_record(Prim, primitive) ->
303 LoopDat2 = prim_up_to_callback(Prim, established, LoopDat),
304 next_state(established, established, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100305
306next_state(State, NewState, LoopDat) when is_record(LoopDat, sctp_state) ->
307 Module = LoopDat#sctp_state.module,
308 case NewState of
309 State ->
310 {next_state, NewState, LoopDat};
311 _ ->
312 ExtState = Module:state_change(State, NewState, LoopDat#sctp_state.ext_state),
313 {next_state, NewState, LoopDat#sctp_state{ext_state = ExtState}}
314 end.