blob: 2cd8b955dfe2ada060e3aa44034670ce49e95b41 [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/>.
19
20-module(sctp_core).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behaviour(gen_fsm).
23
24-include_lib("kernel/include/inet_sctp.hrl").
25-include("osmo_util.hrl").
26
27-export([start_link/1]).
28
29-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
30
31-export([behaviour_info/1]).
32
33% FSM states:
34-export([idle/2, associating/2, established/2]).
35
36behaviour_info(callbacks) ->
Harald Welte91b79652012-01-17 10:12:34 +010037 gen_fsm:behaviour_info(callbacks) ++
38 [{rx_sctp, 4}, {mtp_xfer, 2}, {state_change, 2}, {prim_up, 3}];
Harald Welte26bdef22012-01-16 22:22:17 +010039behaviour_info(Other) ->
40 gen_fsm:behaviour_info(Other).
41
42% Loop Data
43-record(sctp_state, {
44 role, % passive | active
45 state, % idle | associating | established
46 user_pid,
47 sctp_remote_ip,
48 sctp_remote_port,
49 sctp_local_port,
50 sctp_sock,
51 sctp_assoc_id,
52 module, % callback module
53 ext_state % state of the callback module
54 }).
55
56start_link(InitOpts) ->
57 gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]).
58
59reconnect_sctp(L = #sctp_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) ->
60 io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]),
61 timer:sleep(1*1000),
62 InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2},
63 case gen_sctp:connect_init(Sock, Ip, Port, [{active, once}, {reuseaddr, true},
64 {sctp_initmsg, InitMsg}]) of
65 ok ->
66 ok;
67 {error, Error } ->
68 io:format("SCTP Error ~p, reconnecting~n", [Error]),
69 reconnect_sctp(L)
70 end.
71
72init(InitOpts) ->
73 OpenOptsBase = [{active, once}, {reuseaddr, true}],
74 Module = proplists:get_value(module, InitOpts),
75 ModuleArgs = proplists:get_value(module_args, InitOpts),
76 LocalPort = proplists:get_value(sctp_local_port, InitOpts),
77 Role = proplists:get_value(sctp_role, InitOpts),
78 case LocalPort of
79 undefined ->
80 OpenOpts = OpenOptsBase;
81 _ ->
82 OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
83 end,
84 {ok, SctpSock} = gen_sctp:open(OpenOpts),
85 case Module:init(ModuleArgs) of
86 {ok, ExtState} ->
87 LoopDat = #sctp_state{role = Role, sctp_sock = SctpSock,
88 user_pid = proplists:get_value(user_pid, InitOpts),
89 ext_state = ExtState, module = Module,
90 sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
91 sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
92 sctp_local_port = LocalPort},
93 case Role of
94 active ->
95 gen_fsm:send_event(self(), osmo_util:make_prim('M','SCTP_ESTABLISH',request));
96 _ ->
97 ok
98 end,
99 {ok, idle, LoopDat};
100 Default ->
101 {error, {module_returned, Default}}
102 end.
103
104terminate(Reason, State, LoopDat) ->
105 io:format("Terminating ~p (Reason: ~p)~n", [?MODULE, Reason]),
106 Module = LoopDat#sctp_state.module,
107 gen_sctp:close(LoopDat#sctp_state.sctp_sock),
108 Module:terminate(Reason, State, LoopDat#sctp_state.ext_state).
109
110code_change(OldVsn, StateName, LoopDat, Extra) ->
111 Module = LoopDat#sctp_state.module,
112 case Module:code_change(OldVsn, StateName, LoopDat#sctp_state.ext_state, Extra) of
113 {ok, ExtState} ->
114 {ok, StateName, LoopDat#sctp_state{ext_state = ExtState}};
115 Other ->
116 Other
117 end.
118
119% Helper function to send data to the SCTP peer
120send_sctp_to_peer(LoopDat, PktData, StreamId, Ppid) when is_binary(PktData) ->
121 #sctp_state{sctp_sock = Sock, sctp_assoc_id = Assoc} = LoopDat,
122 SndRcvInfo = #sctp_sndrcvinfo{assoc_id = Assoc, ppid = Ppid, stream = StreamId},
123 gen_sctp:send(Sock, SndRcvInfo, PktData).
124
125send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, sctp_state), is_record(Prim, primitive) ->
126 %#m3ua_state{user_fun = Fun, user_args = Args} = LoopDat,
127 %Fun(Prim, Args).
128 UserPid = LoopDat#sctp_state.user_pid,
129 UserPid ! Prim.
130
Harald Welte91b79652012-01-17 10:12:34 +0100131prim_up_to_callback(Prim, State, LoopDat) ->
132 Module = LoopDat#sctp_state.module,
133 case Module:prim_up(Prim, State, LoopDat#sctp_state.ext_state) of
134 {ok, Prim, ExtNew} ->
135 send_prim_to_user(LoopDat, Prim);
136 {ignore, ExtNew} ->
137 ok
138 end,
139 LoopDat#sctp_state{ext_state = ExtNew}.
140
Harald Welte26bdef22012-01-16 22:22:17 +0100141
142handle_event(Event, State, LoopDat) ->
143 Module = LoopDat#sctp_state.module,
144 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
145 case Module:handle_event(Event, State, LoopDat#sctp_state.ext_state) of
146 {next_state, State, ExtState} ->
147 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
148 end.
149
150
151handle_info({sctp, Socket, _RemoteIp, _RemotePort, {ANC, SAC}},
152 State, LoopDat) when is_record(SAC, sctp_assoc_change) ->
153 io:format("SCTP Assoc Change ~p ~p~n", [ANC, SAC]),
154 #sctp_assoc_change{state = SacState, outbound_streams = _OutStreams,
155 inbound_streams = _InStreams, assoc_id = AssocId} = SAC,
156 if
157 SacState == comm_up;
158 SacState == restart ->
159 case State of
160 associating ->
161 NewState = established,
162 Spec = confirm;
163 _ ->
164 NewState = State,
165 Spec = indication
166 end,
167 % primitive to the user
Harald Welte91b79652012-01-17 10:12:34 +0100168 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_ESTABLISH',Spec),
169 State, LoopDat);
Harald Welte26bdef22012-01-16 22:22:17 +0100170 SacState == comm_lost ->
171 case State of
172 releasing ->
173 Spec = confirm;
174 _ ->
175 Spec = indication
176 end,
Harald Welte91b79652012-01-17 10:12:34 +0100177 LoopDat2 = prim_up_to_callback(osmo_util:make_prim('M','SCTP_RELEASE',Spec),
178 State, LoopDat),
Harald Welte26bdef22012-01-16 22:22:17 +0100179 case LoopDat#sctp_state.role of
180 active ->
181 NewState = associating,
Harald Welte91b79652012-01-17 10:12:34 +0100182 reconnect_sctp(LoopDat2);
Harald Welte26bdef22012-01-16 22:22:17 +0100183 _ ->
184 NewState = idle
185 end;
186 SacState == addr_unreachable ->
187 case LoopDat#sctp_state.role of
188 active ->
189 NewState = associating,
190 reconnect_sctp(LoopDat);
191 _ ->
192 NewState = idle
Harald Welte91b79652012-01-17 10:12:34 +0100193 end,
194 LoopDat2 = LoopDat
Harald Welte26bdef22012-01-16 22:22:17 +0100195 end,
196 inet:setopts(Socket, [{active, once}]),
Harald Welte91b79652012-01-17 10:12:34 +0100197 next_state(State, NewState, LoopDat2#sctp_state{sctp_assoc_id = AssocId});
Harald Welte26bdef22012-01-16 22:22:17 +0100198
199handle_info({sctp, Socket, RemoteIp, RemotePort, {[Anc], Data}}, State, LoopDat) ->
200 Module = LoopDat#sctp_state.module,
201 io:format("SCTP rx data: ~p ~p~n", [Anc, Data]),
202 % process incoming SCTP data
203 if Socket == LoopDat#sctp_state.sctp_sock,
204 RemoteIp == LoopDat#sctp_state.sctp_remote_ip,
205 RemotePort == LoopDat#sctp_state.sctp_remote_port ->
206 Ret = Module:rx_sctp(Anc, Data, State, LoopDat#sctp_state.ext_state),
207 case Ret of
208 {ok, Prim, ExtState} ->
209 send_prim_to_user(LoopDat, Prim);
210 {ignore, ExtState} ->
211 ok
212 end;
213 true ->
214 io:format("unknown SCTP: ~p ~p~n", [Anc, Data]),
215 ExtState = LoopDat#sctp_state.ext_state
216 end,
217 inet:setopts(Socket, [{active, once}]),
218 next_state(State, State, LoopDat#sctp_state{ext_state = ExtState});
219
220handle_info({sctp, Socket, RemoteIp, RemotePort, {_Anc, Data}}, State, LoopDat)
221 when is_record(Data, sctp_shutdown_event) ->
222 io:format("SCTP remote ~p:~p shutdown~n", [RemoteIp, RemotePort]),
223 % FIXME: send SCTP_RELEASE.ind ?
224 inet:setopts(Socket, [{active, once}]),
225 case LoopDat#sctp_state.role of
226 active ->
227 reconnect_sctp(LoopDat);
228 _ ->
229 ok
230 end,
231 next_state(State, associating, LoopDat);
232
233handle_info(Info, State, LoopDat) ->
234 Module = LoopDat#sctp_state.module,
235 case Module:handle_info(Info, State, LoopDat#sctp_state.ext_state) of
236 {next_state, State, ExtState} ->
237 {next_state, State, LoopDat#sctp_state{ext_state = ExtState}}
238 end.
239
240
241idle(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100242 % M-SCTP_ESTABLISH.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100243 case LoopDat#sctp_state.role of
244 active ->
245 reconnect_sctp(LoopDat);
246 _ ->
247 ok
248 end,
Harald Welte91b79652012-01-17 10:12:34 +0100249 next_state(idle, associating, LoopDat);
250idle(Prim, LoopDat) when is_record(Prim, primitive) ->
251 LoopDat2 = prim_up_to_callback(Prim, idle, LoopDat),
252 next_state(idle, idle, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100253
254
255
256associating(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
257 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100258 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100259 % directly send RELEASE.conf ?!?
Harald Welte91b79652012-01-17 10:12:34 +0100260 next_state(associating, idle, LoopDat);
261associating(Prim, LoopDat) when is_record(Prim, primitive) ->
262 LoopDat2 = prim_up_to_callback(Prim, associating, LoopDat),
263 next_state(associating, associating, LoopDat2).
264
Harald Welte26bdef22012-01-16 22:22:17 +0100265
266
267established(#primitive{subsystem = 'M', gen_name = 'SCTP_RELEASE',
268 spec_name = request}, LoopDat) ->
Harald Welte91b79652012-01-17 10:12:34 +0100269 % M-SCTP_RELEASE.req from User
Harald Welte26bdef22012-01-16 22:22:17 +0100270 next_state(established, releasing, LoopDat);
271established(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
272 spec_name = request, parameters = Params}, LoopDat) ->
273 % MTP-TRANSFER.req from user app; Send message to remote peer
274 Module = LoopDat#sctp_state.module,
275 ExtState = Module:mtp_xfer(Params, LoopDat#sctp_state.ext_state),
276 next_state(established, established, LoopDat#sctp_state{ext_state = ExtState});
277established(#primitive{subsystem = 'SCTP', gen_name = 'TRANSFER',
278 spec_name = request, parameters = {Stream, Ppid, Data}}, LoopDat) ->
279 io:format("SCTP-TRANSFER.req~n",[]),
280 % somebody (typically callback module) requests us to send SCTP data
281 send_sctp_to_peer(LoopDat, Data, Stream, Ppid),
Harald Welte91b79652012-01-17 10:12:34 +0100282 next_state(established, established, LoopDat);
283established(Prim, LoopDat) when is_record(Prim, primitive) ->
284 LoopDat2 = prim_up_to_callback(Prim, established, LoopDat),
285 next_state(established, established, LoopDat2).
Harald Welte26bdef22012-01-16 22:22:17 +0100286
287next_state(State, NewState, LoopDat) when is_record(LoopDat, sctp_state) ->
288 Module = LoopDat#sctp_state.module,
289 case NewState of
290 State ->
291 {next_state, NewState, LoopDat};
292 _ ->
293 ExtState = Module:state_change(State, NewState, LoopDat#sctp_state.ext_state),
294 {next_state, NewState, LoopDat#sctp_state{ext_state = ExtState}}
295 end.