summaryrefslogtreecommitdiffstats
path: root/src/sctp_m2ua.erl
blob: dfa37964029c8efce39135ae347c9227f322280d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
% M2UA in accordance with RFC3331 (http://tools.ietf.org/html/rfc3331)

% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program.  If not, see <http://www.gnu.org/licenses/>.

-module(sctp_m2ua).
-author('Harald Welte <laforge@gnumonks.org>').
-behaviour(sctp_core).

-include_lib("kernel/include/inet_sctp.hrl").
-include("osmo_util.hrl").
-include("xua.hrl").
-include("m2ua.hrl").
-include("m3ua.hrl").

-define(M2UA_STREAM_USER,	1).

-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).

-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).

-record(m2ua_state, {
		asp_pid,
		last_bsn_received,
		last_fsn_sent
	}).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% gen_fsm callbacks
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

init([Role]) ->
	Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
	AsPid = undefined, % FIXME
	% we use sua_asp module, as m2ua has no difference here
	{ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self(), Role], [{debug, [trace]}]),
	{ok, #m2ua_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff, asp_pid=Asp}}.

terminate(Reason, _State, _LoopDat) ->
	io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
	ok.

code_change(_OldVsn, _State, LoopDat, _Extra) ->
	{ok, LoopDat}.

handle_event(_Event, State, LoopDat) ->
	{next_state, State, LoopDat}.

handle_info(_Info, State, LoopDat) ->
	{next_state, State, LoopDat}.

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% sctp_core callbacks
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
	% confirmation in case of active/connect mode
	Asp = LoopDat#m2ua_state.asp_pid,
	gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
	{ignore, LoopDat};
prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = indication}, State, LoopDat) ->
	% indication in case of passive/listen mode
	{ignore, LoopDat};
prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
	% confirmation in case of active/connect mode
	Asp = LoopDat#m2ua_state.asp_pid,
	gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
	{ignore, LoopDat};

prim_up(Prim, State, LoopDat) ->
	% default: forward all primitives to the user 
	{ok, Prim, LoopDat}.


% sctp_core indicates that we have received some data...
rx_sctp(#sctp_sndrcvinfo{ppid = ?M2UA_PPID}, Data, State, LoopDat) ->
	Asp = LoopDat#m2ua_state.asp_pid,
	M2ua = xua_codec:parse_msg(Data),
	% FIXME: check sequenc number linearity
	case M2ua of
		#xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
			gen_fsm:send_event(Asp, M2ua),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
			gen_fsm:send_event(Asp, M2ua),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_EST_REQ} ->
			% FIXME: respond with M2UA_MAUP_MSGT_EST_CONF
			error_logger:error_report(["unimplemented message",
						   {msg_type, "EST_REQ"}]),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_REL_REQ} ->
			% FIXME: respond with M2UA_MAUP_MSGT_REL_CONF
			error_logger:error_report(["unimplemented message",
						   {msg_type, "REL_REQ"}]),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_STATE_REQ} ->
			handle_m2ua_state_req(M2ua),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_CONG_IND} ->
			% FIXME
			error_logger:error_report(["unimplemented message",
						   {msg_type, "CONG_IND"}]),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_DATA_RETR_REQ} ->
			% FIXME
			error_logger:error_report(["unimplemented message",
						   {msg_type, "RETR_REQ"}]),
			{ignore, LoopDat};
		#xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			  msg_type = ?M2UA_MAUP_MSGT_DATA} ->
			Mtp3 = proplists:get_value(?M2UA_P_M2UA_DATA1, M2ua#xua_msg.payload),
			Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
			{ok, Prim, LoopDat};
		_ ->
			% do something with link related msgs
			io:format("M2UA Unknown message ~p in state ~p~n", [M2ua, State]),
			{ignore, State, LoopDat}
	end.

% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
mtp_xfer(M2ua, LoopDat) when is_record(M2ua, xua_msg) ->
	M2uaBin = xua_codec:encode_msg(M2ua),
	tx_sctp(?M2UA_STREAM_USER, M2uaBin),
	LoopDat;

mtp_xfer(Mtp3, LoopDat) ->
	M2ua = #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
			 msg_type = ?M2UA_MAUP_MSGT_DATA,
			 payload = {?M2UA_P_M2UA_DATA1, length(Mtp3), Mtp3}},
	mtp_xfer(M2ua, LoopDat).

state_change(_, established, LoopDat) ->
	% emulate a 'start' from LSC
	%gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start),
	LoopDat;
state_change(established, _, LoopDat) ->
	%gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure),
	LoopDat;
state_change(_, _, LoopDat) ->
	LoopDat.

handle_m2ua_state_req(M2ua = #xua_msg{payload = Payload}) ->
	{?M2UA_P_MAUP_STATE, State} = lists:keyfind(?M2UA_P_MAUP_STATE, 1, Payload),
	% FIXME handle_m2ua_state_req(State).
	% LOP_SET/CLEAR, EMER_SET/CLEAR, FLUSH_BUFFERSm CONTINUE, CLEAR_RTB, AUDIT, CONG*
	% FIXME: respond with M2UA_MAUP_MSGT_STATE_CONF
	error_logger:error_report(["unimplemented message",
				   {msg_type, "STATE_REQ"}]),
	true.

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% helper functions
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
	Param = {Stream, ?M2UA_PPID, Payload},
	% sent to 'ourselves' (behaviour master module)
	gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).

% callback fun for ASP FMS
asp_prim_to_user(Prim, [SctpPid]) ->
	gen_fsm:send_event(SctpPid, Prim).