blob: b5a455b149de6f1752a1e9e14c71d61ea45d0a21 [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/>.
19
20-module(sctp_sua).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behaviour(sctp_core).
23
24-include_lib("kernel/include/inet_sctp.hrl").
25-include("osmo_util.hrl").
Harald Welte92e783d2012-04-01 19:52:01 +020026-include("xua.hrl").
Harald Welte91b79652012-01-17 10:12:34 +010027-include("sua.hrl").
28-include("m3ua.hrl").
29
30-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
31
32-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
33
34-record(sua_state, {
35 asp_pid
36 }).
37
38%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
39% gen_fsm callbacks
40%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
41
42init(_InitOpts) ->
43 % start SUA ASP
44 Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
45 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
46 {ok, #sua_state{asp_pid=Asp}}.
47
48terminate(Reason, _State, _LoopDat) ->
49 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
50 ok.
51
52code_change(_OldVsn, _State, LoopDat, _Extra) ->
53 {ok, LoopDat}.
54
55handle_event(_Event, State, LoopDat) ->
56 {next_state, State, LoopDat}.
57
58handle_info(_Info, State, LoopDat) ->
59 {next_state, State, LoopDat}.
60
61%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
62% sctp_core callbacks
63%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
64
65prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
66 Asp = LoopDat#sua_state.asp_pid,
67 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
68 {ignore, LoopDat};
69prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
70 Asp = LoopDat#sua_state.asp_pid,
71 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
72 {ignore, LoopDat};
73prim_up(Prim, State, LoopDat) ->
74 % default: forward all primitives to the user
75 {ok, Prim, LoopDat}.
76
77
78% sctp_core indicates that ew have received some data...
79rx_sctp(#sctp_sndrcvinfo{ppid = ?SUA_PPID}, Data, State, LoopDat) ->
80 Asp = LoopDat#sua_state.asp_pid,
Harald Welte92e783d2012-04-01 19:52:01 +020081 Sua = xua_codec:parse_msg(Data),
Harald Welte91b79652012-01-17 10:12:34 +010082 case Sua of
Harald Welte92e783d2012-04-01 19:52:01 +020083 #xua_msg{msg_class = ?M3UA_MSGC_MGMT,
Harald Welte91b79652012-01-17 10:12:34 +010084 msg_type = ?M3UA_MSGT_MGMT_NTFY} ->
85 Prim = osmo_util:make_prim('M','NOTIFY',indication,Sua),
86 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +020087 #xua_msg{msg_class = ?M3UA_MSGC_MGMT,
Harald Welte91b79652012-01-17 10:12:34 +010088 msg_type = ?M3UA_MSGT_MGMT_ERR} ->
89 Prim = osmo_util:make_prim('M','ERROR',indication,Sua),
90 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +020091 #xua_msg{msg_class = ?M3UA_MSGC_SSNM} ->
Harald Weltebd63ade2012-04-01 18:41:53 +020092 % FIXME
Harald Welte91b79652012-01-17 10:12:34 +010093 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +020094 #xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
Harald Welte91b79652012-01-17 10:12:34 +010095 gen_fsm:send_event(Asp, Sua),
96 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +020097 #xua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
Harald Welte91b79652012-01-17 10:12:34 +010098 gen_fsm:send_event(Asp, Sua),
99 {ignore, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200100 #xua_msg{msg_class = ?SUA_MSGC_CL} ->
Harald Weltebd63ade2012-04-01 18:41:53 +0200101 Prim = sua_to_prim(Sua, LoopDat),
102 {ok, Prim, LoopDat};
Harald Welte92e783d2012-04-01 19:52:01 +0200103 %#xua_msg{msg_class = ?SUA_MSGC_C0} ->
Harald Welte91b79652012-01-17 10:12:34 +0100104 _ ->
105 % do something with link related msgs
106 io:format("SUA Unknown message ~p in state ~p~n", [Sua, State]),
107 {ignore, State, LoopDat}
108 end.
109
110% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
Harald Welte92e783d2012-04-01 19:52:01 +0200111mtp_xfer(Sua, LoopDat) when is_record(Sua, xua_msg) ->
112 SuaBin = xua_codec:encode_msg(Sua),
Harald Welte91b79652012-01-17 10:12:34 +0100113 tx_sctp(1, SuaBin),
114 LoopDat.
115
116state_change(_, established, LoopDat) ->
117 % emulate a 'start' from LSC
118 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, start),
119 LoopDat;
120state_change(established, _, LoopDat) ->
121 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, link_failure),
122 LoopDat;
123state_change(_, _, LoopDat) ->
124 LoopDat.
125
126
127%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
128% helper functions
129%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
130
131tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
132 Param = {Stream, ?SUA_PPID, Payload},
133 % sent to 'ourselves' (behaviour master module)
134 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
135
136% callback fun for ASP FMS
137asp_prim_to_user(Prim, [SctpPid]) ->
138 gen_fsm:send_event(SctpPid, Prim).
Harald Weltebd63ade2012-04-01 18:41:53 +0200139
140
Harald Welte92e783d2012-04-01 19:52:01 +0200141sua_to_prim(Sua, LoopDat) when is_record(Sua, xua_msg) ->
Harald Weltebd63ade2012-04-01 18:41:53 +0200142 Sccp = sua_sccp_conv:sua_to_sccp(Sua),
143 osmo_util:make_prim('N','UNITADATA',indication, Sccp).