blob: 8a2d7c456335845aa104ff073d8b5f71fc7eac93 [file] [log] [blame]
Harald Welteee7964c2012-05-07 23:55:02 +02001% M2UA in accordance with RFC3331 (http://tools.ietf.org/html/rfc3331)
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_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").
26-include("m2ua.hrl").
27
28-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
29
30-export([rx_sctp/4, mtp_xfer/2, state_change/3, prim_up/3]).
31
32-record(m2ua_state, {
33 asp_pid,
34 last_bsn_received,
35 last_fsn_sent
36 }).
37
38%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
39% gen_fsm callbacks
40%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
41
42init(_InitOpts) ->
43 {ok, Asp} = gen_fsm:start_link(xua_asp_fsm, [sua_asp, [], Fun, [self()], self()], [{debug, [trace]}]),
44 {ok, #m2ua_state{last_bsn_received=16#ffffff, last_fsn_sent=16#ffffff, asp_pid=Asp}}
45
46terminate(Reason, _State, _LoopDat) ->
47 io:format("Terminating ~p (Reason ~p)~n", [?MODULE, Reason]),
48 ok.
49
50code_change(_OldVsn, _State, LoopDat, _Extra) ->
51 {ok, LoopDat}.
52
53handle_event(_Event, State, LoopDat) ->
54 {next_state, State, LoopDat}.
55
56handle_info(_Info, State, LoopDat) ->
57 {next_state, State, LoopDat}.
58
59%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
60% sctp_core callbacks
61%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
62
63prim_up(#primitive{subsystem='M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, State, LoopDat) ->
64 Asp = LoopDat#m2ua_state.asp_pid,
65 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_UP',request)),
66 {ignore, LoopDat};
67prim_up(#primitive{subsystem='M', gen_name = 'ASP_UP', spec_name = confirm}, State, LoopDat) ->
68 Asp = LoopDat#m2ua_state.asp_pid,
69 gen_fsm:send_event(Asp, osmo_util:make_prim('M','ASP_ACTIVE',request)),
70 {ignore, LoopDat};
71prim_up(Prim, State, LoopDat) ->
72 % default: forward all primitives to the user
73 {ok, Prim, LoopDat}.
74
75
76% sctp_core indicates that we have received some data...
77rx_sctp(#sctp_sndrcvinfo{ppid = ?M2UA_PPID}, Data, State, LoopDat) ->
78 Asp = LoopDat#m2ua_state.asp_pid,
79 {ok, M2ua} = xua_codec:parse_msg(Data),
80 % FIXME: check sequenc number linearity
81 case M2ua of
82 #xua_msg{msg_class = ?M3UA_MSGC_SSNM} ->
83 % FIXME
84 {ignore, LoopDat};
85 #xua_msg{msg_class = ?M3UA_MSGC_ASPSM} ->
86 gen_fsm:send_event(Asp, M2ua),
87 {ignore, LoopDat};
88 #xua_msg{msg_class = ?M3UA_MSGC_ASPTM} ->
89 gen_fsm:send_event(Asp, M2ua),
90 {ignore, LoopDat};
91 #xua_msg{msg_class = ?M2UA_CLASS_M2UA,
92 msg_type = ?M2UA_TYPE_USER} ->
93 Mtp3 = M2pa#m2pa_msg.mtp3,
94 case LoopDat#m2pa_state.msu_fisu_accepted of
95 1 ->
96 LoopDat2 = LoopDat#m2pa_state{last_bsn_received = FsnRecv},
97 case Mtp3 of
98 undefined ->
99 ok;
100 _ ->
101 send_userdata_ack(LoopDat2)
102 end,
103 gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, fisu_msu_received),
104 Prim = osmo_util:make_prim('MTP','TRANSFER',indication, Mtp3),
105 {ok, Prim, LoopDat2};
106 _ ->
107 {ignore, LoopDat}
108 end;
109 _ ->
110 % do something with link related msgs
111 io:format("M2UA Unknown message ~p in state ~p~n", [M2pa, State]),
112 {ignore, State, LoopDat}
113 end.
114
115% MTP-TRANSFER.req has arrived at sctp_core, encapsulate+tx it
116mtp_xfer(Mtp3, LoopDat) ->
117 Fsn = inc_seq_nr(LoopDat#m2pa_state.last_fsn_sent),
118 M2ua = #xua_msg{msg_class = ?M2UA_CLASS_M2UA,
119 msg_type = ?M2UA_TYPE_USER,
120 mtp3 = Mtp3},
121 M2paBin = xua_codec:encode_msg(M2ua),
122 tx_sctp(?M2UA_STREAM_USER, M2paBin),
123 LoopDat2.
124
125state_change(_, established, LoopDat) ->
126 % emulate a 'start' from LSC
127 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, start),
128 LoopDat;
129state_change(established, _, LoopDat) ->
130 %gen_fsm:send_event(LoopDat#m2pa_state.lsc_pid, link_failure),
131 LoopDat;
132state_change(_, _, LoopDat) ->
133 LoopDat.
134
135
136%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
137% helper functions
138%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
139
140tx_sctp(Stream, Payload) when is_integer(Stream), is_binary(Payload) ->
141 Param = {Stream, ?M2UA_PPID, Payload},
142 % sent to 'ourselves' (behaviour master module)
143 gen_fsm:send_event(self(), osmo_util:make_prim('SCTP','TRANSFER',request,Param)).