blob: a02f70cf8ddcbefe17ced13e830cca4fada034dd [file] [log] [blame]
Harald Welte475ccdb2012-01-17 10:11:58 +01001% SCCP M3UA / SUA ASP gsn_fsm according to RFC3868 4.3.1
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(xua_asp_fsm).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behaviour(gen_fsm).
23
24-include("osmo_util.hrl").
25-include("m3ua.hrl").
26
27% gen_fsm exports
28-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
29
30% states in this FSM
31-export([asp_down/2, asp_inactive/2, asp_active/2]).
32
33% helper functions exporte to callback modules
34-export([send_sctp_to_peer/2, send_prim_to_user/2]).
35
36-export([behaviour_info/1]).
37
38behaviour_info(callbacks) ->
39 [{gen_xua_msg, 3}, {asp_down, 3}, {asp_inactive, 3}, {asp_active, 3}].
40
41% Timeouts in milliseconds
42-define(T_ACK_TIMEOUT, 2*60*100).
43
44-record(asp_state, {
45 module,
46 role,
47 t_ack,
48 ext_state,
49 user_fun,
50 user_args,
51 sctp_pid
52 }).
53
54%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
55% gen_fsm callbacks
56%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
57
58init([Module, ModuleArgs, UserFun, UserArgs, SctpPid]) ->
59 {ok, ExtState} = Module:init(ModuleArgs),
60 AspState = #asp_state{module = Module,
61 user_fun = UserFun,
62 user_args = UserArgs,
63 ext_state = ExtState,
64 sctp_pid = SctpPid,
65 role = asp},
66 {ok, asp_down, AspState}.
67
68terminate(Reason, State, _LoopDat) ->
69 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
70 [?MODULE, State, Reason]),
71 ok.
72
73code_change(_OldVsn, StateName, LoopDat, _Extra) ->
74 {ok, StateName, LoopDat}.
75
76handle_event(Event, State, LoopDat) ->
77 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
78 {next_state, State, LoopDat}.
79
80
81handle_info(Info, State, LoopDat) ->
82 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
83 {next_state, State, LoopDat}.
84
85
86%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
87% STATE "asp_down"
88%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
89
90asp_down(#primitive{subsystem = 'M', gen_name = 'ASP_UP',
91 spec_name = request, parameters = _Params}, LoopDat) ->
92 % M-ASP_UP.req from user, generate message and send to remote peer
93 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, []);
94asp_down({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params}}, LoopDat) ->
95 send_msg_start_tack(LoopDat, asp_down, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP, Params);
96
97asp_down({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPUP_ACK}, LoopDat) ->
98 timer:cancel(LoopDat#asp_state.t_ack),
99 % transition into ASP_INACTIVE
100 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_UP',confirm)),
101 {next_state, asp_inactive, LoopDat};
102
103asp_down(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
104 Module:asp_down(WhateverElse, ExtState, LoopDat).
105
106
107%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
108% STATE "asp_inactive"
109%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
110
111asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE',
112 spec_name = request, parameters = Params}, LoopDat) ->
113 % M-ASP_ACTIVE.req from user, generate message and send to remote peer
114 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC,
115 Params);
116
117asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params}}, LoopDat) ->
118 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC, Params);
119
120asp_inactive(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
121 spec_name = request, parameters = _Params}, LoopDat) ->
122 % M-ASP_DOWN.req from user, generate message and send to remote peer
123 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
124
125asp_inactive({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
126 send_msg_start_tack(LoopDat, asp_inactive, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
127
128asp_inactive({xua_msg,?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPAC_ACK}, LoopDat) ->
129 timer:cancel(LoopDat#asp_state.t_ack),
130 % transition into ASP_ACTIVE
131 % signal this to the user
132 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_ACTIVE',confirm)),
133 {next_state, asp_active, LoopDat};
134
135asp_inactive({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
136 timer:cancel(LoopDat#asp_state.t_ack),
137 % transition into ASP_DOWN
138 % signal this to the user
139 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
140 {next_state, asp_down, LoopDat};
141
142asp_inactive(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
143 Module:asp_inactive(WhateverElse, ExtState, LoopDat).
144
145
146%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
147% STATE "asp_active"
148%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
149
150asp_active({xua_msg, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN_ACK}, LoopDat) ->
151 timer:cancel(LoopDat#asp_state.t_ack),
152 % transition into ASP_DOWN
153 % signal this to the user
154 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_DOWN',confirm)),
155 {next_state, asp_down, LoopDat};
156
157asp_active({xua_msg, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA_ACK}, LoopDat) ->
158 timer:cancel(LoopDat#asp_state.t_ack),
159 % transition into ASP_INACTIVE
160 % signal this to the user
161 send_prim_to_user(LoopDat, osmo_util:make_prim('M','ASP_INACTIVE',confirm)),
162 {next_state, asp_inactive, LoopDat};
163
164asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN',
165 spec_name = request, parameters = _Params}, LoopDat) ->
166 % M-ASP_DOWN.req from user, generate message and send to remote peer
167 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, []);
168
169asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params}}, LoopDat) ->
170 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPSM, ?M3UA_MSGT_ASPSM_ASPDN, Params);
171
172asp_active(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE',
173 spec_name = request, parameters = _Params}, LoopDat) ->
174 % M-ASP_INACTIVE.req from user, generate message and send to remote peer
175 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, []);
176
177asp_active({timer_expired, t_ack, {?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params}}, LoopDat) ->
178 send_msg_start_tack(LoopDat, asp_active, ?M3UA_MSGC_ASPTM, ?M3UA_MSGT_ASPTM_ASPIA, Params);
179
180asp_active(#primitive{subsystem = 'MTP', gen_name = 'TRANSFER',
181 spec_name = request, parameters = Params}, LoopDat) ->
182 % MTP-TRANSFER.req from user app: Send message to remote peer
183 OptList = [{?M3UA_IEI_PROTOCOL_DATA, Params}],
184 Msg = #m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
185 msg_type = ?M3UA_MSGT_XFR_DATA,
186 payload = OptList},
187 send_sctp_to_peer(LoopDat, Msg),
188 {next_state, asp_active, LoopDat};
189asp_active(#m3ua_msg{version = 1, msg_class = ?M3UA_MSGC_TRANSFER,
190 msg_type = ?M3UA_MSGT_XFR_DATA, payload = Params}, LoopDat) ->
191 % Data transfer from remote entity: Send MTP-TRANSFER.ind primitive to the user
192 Mtp3 = proplists:get_value(?M3UA_IEI_PROTOCOL_DATA, Params),
193 send_prim_to_user(LoopDat, osmo_util:make_prim('MTP','TRANSFER',indication,Mtp3)),
194 {next_state, asp_active, LoopDat};
195
196asp_active(WhateverElse, LoopDat = #asp_state{module = Module, ext_state = ExtState}) ->
197 Module:asp_active(WhateverElse, ExtState, LoopDat).
198
199
200%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
201% helper functions
202%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
203
204% helper to send one of the up/down/act/inact management messages + start timer
205send_msg_start_tack(LoopDat, State, MsgClass, MsgType, Params) ->
206 Module = LoopDat#asp_state.module,
207 % generate and send the respective message
208 %Msg = #m3ua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params},
209 Msg = Module:gen_xua_msg(MsgClass, MsgType, Params),
210 send_sctp_to_peer(LoopDat, Msg),
211 % start T(ack) timer and wait for ASP_UP_ACK
212 timer:cancel(LoopDat#asp_state.t_ack),
213 {ok, Tack} = timer:apply_after(?T_ACK_TIMEOUT, gen_fsm, send_event,
214 [self(), {timer_expired, t_ack, {MsgClass, MsgType, Params}}]),
215 {next_state, State, LoopDat#asp_state{t_ack = Tack}}.
216
217
218send_prim_to_user(LoopDat, Prim) when is_record(LoopDat, asp_state),
219 is_record(Prim, primitive) ->
220 #asp_state{user_fun = Fun, user_args = Args} = LoopDat,
221 Fun(Prim, Args).
222
223
224% Helper function to send data to the SCTP peer
225send_sctp_to_peer(LoopDat, Msg) ->
226 Prim = osmo_util:make_prim('MTP','TRANSFER',request, Msg),
227 gen_fsm:send_event(LoopDat#asp_state.sctp_pid, Prim).