blob: 039f1bdab2d4158f540a8e8af591c67c29df92fb [file] [log] [blame]
Harald Welteee7964c2012-05-07 23:55:02 +02001% M2UA in accordance with RFC3331 (http://tools.ietf.org/html/rfc3331)
2
Harald Welte0d8af6b2013-07-27 15:02:17 +08003% (C) 2011-2013 by Harald Welte <laforge@gnumonks.org>
Harald Welteee7964c2012-05-07 23:55:02 +02004%
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_m2ua).
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 Weltee58b38f2012-05-30 12:05:18 +020026-include("xua.hrl").
Harald Welteee7964c2012-05-07 23:55:02 +020027-include("m2ua.hrl").
Harald Weltee58b38f2012-05-30 12:05:18 +020028-include("m3ua.hrl").
Harald Welteee7964c2012-05-07 23:55:02 +020029
Harald Welte0d8af6b2013-07-27 15:02:17 +080030-define(M2UA_STREAM_USER, 1).
31
Harald Welteee7964c2012-05-07 23:55:02 +020032-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
33
34-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
35
36-record(m2ua_state, {
37 asp_pid,
38 last_bsn_received,
39 last_fsn_sent
40 }).
41
42%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
43% gen_fsm callbacks
44%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
45
Harald Welte0d8af6b2013-07-27 15:02:17 +080046init([Role]) ->
47 Fun = fun(Prim, Args) -> asp_prim_to_user(Prim, Args) end,
48 AsPid = undefined, % FIXME
49 % we use sua_asp module, as m2ua has no difference here
50 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [AsPid, sua_asp, [], Fun, [self()], self(), Role], [{debug, [trace]}]),
Harald Weltee58b38f2012-05-30 12:05:18 +020051 {ok, #m2ua_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff, asp_pid=Asp}}.
Harald Welteee7964c2012-05-07 23:55:02 +020052
53terminate(Reason, _State, _LoopDat) ->
54 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
55 ok.
56
57code_change(_OldVsn, _State, LoopDat, _Extra) ->
58 {ok, LoopDat}.
59
60handle_event(_Event, State, LoopDat) ->
61 {next_state, State, LoopDat}.
62
63handle_info(_Info, State, LoopDat) ->
64 {next_state, State, LoopDat}.
65
66%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
67% sctp_core callbacks
68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69
70prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
Harald Welte0d8af6b2013-07-27 15:02:17 +080071 % confirmation in case of active/connect mode
Harald Welteee7964c2012-05-07 23:55:02 +020072 Asp = LoopDat#m2ua_state.asp_pid,
73 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
74 {ignore, LoopDat};
Harald Welte0d8af6b2013-07-27 15:02:17 +080075prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = indication}, State, LoopDat) ->
76 % indication in case of passive/listen mode
77 Asp = LoopDat#m2ua_state.asp_pid,
78 {ignore, LoopDat};
Harald Welteee7964c2012-05-07 23:55:02 +020079prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
80 Asp = LoopDat#m2ua_state.asp_pid,
81 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
82 {ignore, LoopDat};
83prim_up(Prim, State, LoopDat) ->
84 % default: forward all primitives to the user
85 {ok, Prim, LoopDat}.
86
87
88% sctp_core indicates that we have received some data...
89rx_sctp(#sctp_sndrcvinfo{ppid = ?M2UA_PPID}, Data, State, LoopDat) ->
90 Asp = LoopDat#m2ua_state.asp_pid,
Harald Welte0d8af6b2013-07-27 15:02:17 +080091 M2ua = xua_codec:parse_msg(Data),
Harald Welteee7964c2012-05-07 23:55:02 +020092 % FIXME: check sequenc number linearity
93 case M2ua of
Harald Welteee7964c2012-05-07 23:55:02 +020094 #xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
95 gen_fsm:send_event(Asp, M2ua),
96 {ignore, LoopDat};
97 #xua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
98 gen_fsm:send_event(Asp, M2ua),
99 {ignore, LoopDat};
Harald Weltee58b38f2012-05-30 12:05:18 +0200100 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
101 msg_type = ?M2UA_MAUP_MSGT_EST_REQ} ->
102 % FIXME: respond with M2UA_MAUP_MSGT_EST_CONF
103 error_logger:error_report(["unimplemented message",
104 {msg_type, "EST_REQ"}]),
105 {ignore, LoopDat};
106 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
107 msg_type = ?M2UA_MAUP_MSGT_REL_REQ} ->
108 % FIXME: respond with M2UA_MAUP_MSGT_REL_CONF
109 error_logger:error_report(["unimplemented message",
110 {msg_type, "REL_REQ"}]),
111 {ignore, LoopDat};
112 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
113 msg_type = ?M2UA_MAUP_MSGT_STATE_REQ} ->
114 handle_m2ua_state_req(M2ua),
115 {ignore, LoopDat};
116 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
117 msg_type = ?M2UA_MAUP_MSGT_CONG_IND} ->
118 % FIXME
119 error_logger:error_report(["unimplemented message",
120 {msg_type, "CONG_IND"}]),
121 {ignore, LoopDat};
122 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
123 msg_type = ?M2UA_MAUP_MSGT_DATA_RETR_REQ} ->
124 % FIXME
125 error_logger:error_report(["unimplemented message",
126 {msg_type, "RETR_REQ"}]),
127 {ignore, LoopDat};
128 #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
129 msg_type = ?M2UA_MAUP_MSGT_DATA} ->
130 Mtp3 = proplists:get_value(?M2UA_P_M2UA_DATA1, M2ua#xua_msg.payload),
131 Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
Harald Welte0d8af6b2013-07-27 15:02:17 +0800132 {ok, Prim, LoopDat};
Harald Welteee7964c2012-05-07 23:55:02 +0200133 _ ->
134 % do something with link related msgs
Harald Weltee58b38f2012-05-30 12:05:18 +0200135 io:format("M2UA Unknown message ~p in state ~p~n", [M2ua, State]),
Harald Welteee7964c2012-05-07 23:55:02 +0200136 {ignore, State, LoopDat}
137 end.
138
139% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
Harald Welte0d8af6b2013-07-27 15:02:17 +0800140mtp_xfer(M2ua, LoopDat) when is_record(M2ua, xua_msg) ->
141 M2uaBin = xua_codec:encode_msg(M2ua),
142 tx_sctp(?M2UA_STREAM_USER, M2uaBin),
143 LoopDat;
144
Harald Welteee7964c2012-05-07 23:55:02 +0200145mtp_xfer(Mtp3, LoopDat) ->
Harald Weltee58b38f2012-05-30 12:05:18 +0200146 M2ua = #xua_msg{msg_class = ?M2UA_MSGC_MAUP,
147 msg_type = ?M2UA_MAUP_MSGT_DATA,
148 payload = {?M2UA_P_M2UA_DATA1, length(Mtp3), Mtp3}},
Harald Welte0d8af6b2013-07-27 15:02:17 +0800149 mtp_xfer(M2ua, LoopDat).
Harald Welteee7964c2012-05-07 23:55:02 +0200150
151state_change(_, established, LoopDat) ->
152 % emulate a 'start' from LSC
153 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start),
154 LoopDat;
155state_change(established, _, LoopDat) ->
156 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure),
157 LoopDat;
158state_change(_, _, LoopDat) ->
159 LoopDat.
160
Harald Weltee58b38f2012-05-30 12:05:18 +0200161handle_m2ua_state_req(M2ua = #xua_msg{payload = Payload}) ->
162 {?M2UA_P_MAUP_STATE, State} = lists:keyfind(?M2UA_P_MAUP_STATE, 1, Payload),
163 % FIXME handle_m2ua_state_req(State).
164 % LOP_SET/CLEAR, EMER_SET/CLEAR, FLUSH_BUFFERSm CONTINUE, CLEAR_RTB, AUDIT, CONG*
165 % FIXME: respond with M2UA_MAUP_MSGT_STATE_CONF
166 error_logger:error_report(["unimplemented message",
167 {msg_type, "STATE_REQ"}]),
168 true.
Harald Welteee7964c2012-05-07 23:55:02 +0200169
170%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
171% helper functions
172%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
173
174tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
175 Param = {Stream, ?M2UA_PPID, Payload},
176 % sent to 'ourselves' (behaviour master module)
177 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).
Harald Welte0d8af6b2013-07-27 15:02:17 +0800178
179% callback fun for ASP FMS
180asp_prim_to_user(Prim, [SctpPid]) ->
181 gen_fsm:send_event(SctpPid, Prim).