blob: 0d35780923bd8563e485f77eebcd5ddb639390ff [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").
26-include("sua.hrl").
27-include("m3ua.hrl").
28
29-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
30
31-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
32
33-record(sua_state, {
34 asp_pid
35 }).
36
37%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
38% gen_fsm callbacks
39%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
40
41init(_InitOpts) ->
42 % start SUA ASP
43 Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
44 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
45 {ok, #sua_state{asp_pid=Asp}}.
46
47terminate(Reason, _State, _LoopDat) ->
48 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
49 ok.
50
51code_change(_OldVsn, _State, LoopDat, _Extra) ->
52 {ok, LoopDat}.
53
54handle_event(_Event, State, LoopDat) ->
55 {next_state, State, LoopDat}.
56
57handle_info(_Info, State, LoopDat) ->
58 {next_state, State, LoopDat}.
59
60%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
61% sctp_core callbacks
62%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
63
64prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
65 Asp = LoopDat#sua_state.asp_pid,
66 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
67 {ignore, LoopDat};
68prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
69 Asp = LoopDat#sua_state.asp_pid,
70 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
71 {ignore, LoopDat};
72prim_up(Prim, State, LoopDat) ->
73 % default: forward all primitives to the user
74 {ok, Prim, LoopDat}.
75
76
77% sctp_core indicates that ew have received some data...
78rx_sctp(#sctp_sndrcvinfo{ppid = ?SUA_PPID}, Data, State, LoopDat) ->
79 Asp = LoopDat#sua_state.asp_pid,
80 Sua = sua_codec:parse_msg(Data),
81 case Sua of
82 #sua_msg{msg_class = ?M3UA_MSGC_MGMT,
83 msg_type = ?M3UA_MSGT_MGMT_NTFY} ->
84 Prim = osmo_util:make_prim('M','NOTIFY',indication,Sua),
85 {ok, Prim, LoopDat};
86 #sua_msg{msg_class = ?M3UA_MSGC_MGMT,
87 msg_type = ?M3UA_MSGT_MGMT_ERR} ->
88 Prim = osmo_util:make_prim('M','ERROR',indication,Sua),
89 {ok, Prim, LoopDat};
90 #sua_msg{msg_class = ?M3UA_MSGC_SSNM} ->
Harald Weltebd63ade2012-04-01 18:41:53 +020091 % FIXME
Harald Welte91b79652012-01-17 10:12:34 +010092 {ignore, LoopDat};
93 #sua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
94 gen_fsm:send_event(Asp, Sua),
95 {ignore, LoopDat};
96 #sua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
97 gen_fsm:send_event(Asp, Sua),
98 {ignore, LoopDat};
Harald Weltebd63ade2012-04-01 18:41:53 +020099 #sua_msg{msg_class = ?SUA_MSGC_CL} ->
100 Prim = sua_to_prim(Sua, LoopDat),
101 {ok, Prim, LoopDat};
102 %#sua_msg{msg_class = ?SUA_MSGC_C0} ->
Harald Welte91b79652012-01-17 10:12:34 +0100103 _ ->
104 % do something with link related msgs
105 io:format("SUA Unknown message ~p in state ~p~n", [Sua, State]),
106 {ignore, State, LoopDat}
107 end.
108
109% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
110mtp_xfer(Sua, LoopDat) when is_record(Sua, sua_msg) ->
111 SuaBin = sua_codec:encode_msg(Sua),
112 tx_sctp(1, SuaBin),
113 LoopDat.
114
115state_change(_, established, LoopDat) ->
116 % emulate a 'start' from LSC
117 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, start),
118 LoopDat;
119state_change(established, _, LoopDat) ->
120 %gen_fsm:send_event(LoopDat#sua_state.lsc_pid, link_failure),
121 LoopDat;
122state_change(_, _, LoopDat) ->
123 LoopDat.
124
125
126%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
127% helper functions
128%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
129
130tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
131 Param = {Stream, ?SUA_PPID, Payload},
132 % sent to 'ourselves' (behaviour master module)
133 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
134
135% callback fun for ASP FMS
136asp_prim_to_user(Prim, [SctpPid]) ->
137 gen_fsm:send_event(SctpPid, Prim).
Harald Weltebd63ade2012-04-01 18:41:53 +0200138
139
140sua_to_prim(Sua, LoopDat) when is_record(Sua, sua_msg) ->
141 Sccp = sua_sccp_conv:sua_to_sccp(Sua),
142 osmo_util:make_prim('N','UNITADATA',indication, Sccp).