blob: 9b8cc96ff247be121349ec37dd2714b5dd8fa1a6 [file] [log] [blame]
Harald Welte91b79652012-01-17 10:12:34 +01001% SUA behaviour call-back for sctp_core
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 Welte91b79652012-01-17 10:12:34 +010033
34-module(sctp_sua).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(sctp_core).
37
38-include_lib("kernel/include/inet_sctp.hrl").
39-include("osmo_util.hrl").
Harald Welte92e783d2012-04-01 19:52:01 +020040-include("xua.hrl").
Harald Welte91b79652012-01-17 10:12:34 +010041-include("sua.hrl").
42-include("m3ua.hrl").
43
44-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
45
46-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
47
48-record(sua_state, {
49 asp_pid
50 }).
51
52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
53% gen_fsm callbacks
54%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
55
56init(_InitOpts) ->
57 % start SUA ASP
58 Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
59 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
60 {ok, #sua_state{asp_pid=Asp}}.
61
62terminate(Reason, _State, _LoopDat) ->
63 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
64 ok.
65
66code_change(_OldVsn, _State, LoopDat, _Extra) ->
67 {ok, LoopDat}.
68
69handle_event(_Event, State, LoopDat) ->
70 {next_state, State, LoopDat}.
71
72handle_info(_Info, State, LoopDat) ->
73 {next_state, State, LoopDat}.
74
75%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
76% sctp_core callbacks
77%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78
79prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
80 Asp = LoopDat#sua_state.asp_pid,
81 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
82 {ignore, LoopDat};
83prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
84 Asp = LoopDat#sua_state.asp_pid,
85 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
86 {ignore, LoopDat};
87prim_up(Prim, State, LoopDat) ->
88 % default: forward all primitives to the user
89 {ok, Prim, LoopDat}.
90
91
92% sctp_core indicates that ew have received some data...
93rx_sctp(#sctp_sndrcvinfo{ppid = ?SUA_PPID}, Data, State, LoopDat) ->
94 Asp = LoopDat#sua_state.asp_pid,
Harald Welte92e783d2012-04-01 19:52:01 +020095 Sua = xua_codec:parse_msg(Data),
Harald Welte91b79652012-01-17 10:12:34 +010096 case Sua of
Harald Welte92e783d2012-04-01 19:52:01 +020097 #xua_msg{msg_class = ?M3UA_MSGC_MGMT,
Harald Welte91b79652012-01-17 10:12:34 +010098 msg_type = ?M3UA_MSGT_MGMT_NTFY} ->
99 Prim = osmo_util:make_prim('M','NOTIFY',indication,Sua),
100 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200101 #xua_msg{msg_class = ?M3UA_MSGC_MGMT,
Harald Welte91b79652012-01-17 10:12:34 +0100102 msg_type = ?M3UA_MSGT_MGMT_ERR} ->
103 Prim = osmo_util:make_prim('M','ERROR',indication,Sua),
104 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200105 #xua_msg{msg_class = ?M3UA_MSGC_SSNM} ->
Harald Weltebd63ade2012-04-01 18:41:53 +0200106 % FIXME
Harald Welte91b79652012-01-17 10:12:34 +0100107 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200108 #xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
Harald Welte91b79652012-01-17 10:12:34 +0100109 gen_fsm:send_event(Asp, Sua),
110 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200111 #xua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
Harald Welte91b79652012-01-17 10:12:34 +0100112 gen_fsm:send_event(Asp, Sua),
113 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200114 #xua_msg{msg_class = ?SUA_MSGC_CL} ->
Harald Weltebd63ade2012-04-01 18:41:53 +0200115 Prim = sua_to_prim(Sua, LoopDat),
116 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200117 %#xua_msg{msg_class = ?SUA_MSGC_C0} ->
Harald Welte91b79652012-01-17 10:12:34 +0100118 _ ->
119 % do something with link related msgs
120 io:format("SUA Unknown message ~p in state ~p~n", [Sua, State]),
121 {ignore, State, LoopDat}
122 end.
123
124% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
Harald Welte92e783d2012-04-01 19:52:01 +0200125mtp_xfer(Sua, LoopDat) when is_record(Sua, xua_msg) ->
126 SuaBin = xua_codec:encode_msg(Sua),
Harald Welte91b79652012-01-17 10:12:34 +0100127 tx_sctp(1, SuaBin),
128 LoopDat.
129
130state_change(_, established, LoopDat) ->
131 % emulate a 'start' from LSC
132 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, start),
133 LoopDat;
134state_change(established, _, LoopDat) ->
135 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, link_failure),
136 LoopDat;
137state_change(_, _, LoopDat) ->
138 LoopDat.
139
140
141%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
142% helper functions
143%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
144
145tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
146 Param = {Stream, ?SUA_PPID, Payload},
147 % sent to 'ourselves' (behaviour master module)
148 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
149
150% callback fun for ASP FMS
151asp_prim_to_user(Prim, [SctpPid]) ->
152 gen_fsm:send_event(SctpPid, Prim).
Harald Weltebd63ade2012-04-01 18:41:53 +0200153
154
Harald Welte92e783d2012-04-01 19:52:01 +0200155sua_to_prim(Sua, LoopDat) when is_record(Sua, xua_msg) ->
Harald Weltebd63ade2012-04-01 18:41:53 +0200156 Sccp = sua_sccp_conv:sua_to_sccp(Sua),
157 osmo_util:make_prim('N','UNITADATA',indication, Sccp).