blob: 9380f8e03561d85d2deb0ad5b91b739bda332610 [file] [log] [blame]
Harald Weltefbd4f732012-05-06 23:29:42 +02001% M2UA / M3UA / SUA AS 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% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
33
34-module(xua_as_fsm).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(gen_fsm).
37
38-include("osmo_util.hrl").
39-include("m3ua.hrl").
40
41% gen_fsm exports
Harald Welteee7964c2012-05-07 23:55:02 +020042-export([init/1, terminate/3, code_change/4, handle_event/3, handle_sync_event/4, handle_info/3]).
Harald Weltefbd4f732012-05-06 23:29:42 +020043
44% states in this FSM
45-export([as_down/2, as_inactive/2, as_active/2, as_pending/2]).
46
Harald Welte7c3ec172012-05-08 23:36:49 +020047% exported API
48-export([create_asp/2]).
49
Harald Weltefbd4f732012-05-06 23:29:42 +020050% Timeouts in milliseconds
51-define(T_R_TIMEOUT, 2*60*100).
52
53-record(as_state, {
Harald Welteee7964c2012-05-07 23:55:02 +020054 as_sup_pid,
Harald Weltefbd4f732012-05-06 23:29:42 +020055 role,
56 t_r,
57 asp_list
58 }).
59
Harald Welte7c3ec172012-05-08 23:36:49 +020060create_asp(Name, AspFsmArgs) ->
61 AsFsmName = sg_as_sup:get_as_fsm_name(Name),
62 gen_fsm:sync_send_all_state_event(AsFsmName, {create_asp, AspFsmArgs}).
63
Harald Weltefbd4f732012-05-06 23:29:42 +020064%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
65% gen_fsm callbacks
66%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
67
Harald Welteee7964c2012-05-07 23:55:02 +020068init([AsSupPid]) when is_pid(AsSupPid) ->
Harald Weltefbd4f732012-05-06 23:29:42 +020069 AsState = #as_state{asp_list = [],
Harald Welteee7964c2012-05-07 23:55:02 +020070 as_sup_pid = AsSupPid,
Harald Weltefbd4f732012-05-06 23:29:42 +020071 role = sg},
72 {ok, as_down, AsState}.
73
74terminate(Reason, State, _LoopDat) ->
75 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
76 [?MODULE, State, Reason]),
77 ok.
78
79code_change(_OldVsn, StateName, LoopDat, _Extra) ->
80 {ok, StateName, LoopDat}.
81
Harald Welteee7964c2012-05-07 23:55:02 +020082handle_sync_event({create_asp, Args}, From, State, LoopDat) ->
83 % resolve the ASP supervisor PID
84 AsSupPid = LoopDat#as_state.as_sup_pid,
85 AsChildList = supervisor:which_children(AsSupPid),
86 io:format("AsSupPid ~p, ChildList ~p~n", [AsSupPid, AsChildList]),
87 {asp_sup, AspSupPid, _, _} = lists:keyfind(asp_sup, 1, AsChildList),
88 % actually tell it to start a new ASP, prepend our own Pid
89 Ret = supervisor:start_child(AspSupPid, [self()|Args]),
90 LoopDatOut = case Ret of
91 {ok, AspPid} ->
92 link(AspPid),
93 LoopDat#as_state{asp_list = [AspPid|LoopDat#as_state.asp_list]};
94 {ok, AspPid, _} ->
95 link(AspPid),
96 LoopDat#as_state{asp_list = [AspPid|LoopDat#as_state.asp_list]};
97 _ ->
98 LoopDat
99 end,
100 {reply, Ret, State, LoopDatOut}.
101
Harald Weltefbd4f732012-05-06 23:29:42 +0200102handle_event(Event, State, LoopDat) ->
103 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
104 {next_state, State, LoopDat}.
105
106handle_info({'EXIT', Pid, Reason}, State, LoopDat) ->
107 io:format("EXIT from Process ~p (~p), cleaning up ASP list~n",
108 [Pid, Reason]),
109 % FIXME: send fake ASP-DOWN event about ASP to self
Harald Welteee7964c2012-05-07 23:55:02 +0200110 NewAspList = lists:delete(Pid, LoopDat#as_state.asp_list),
111 {next_state, State, LoopDat#as_state{asp_list = NewAspList}};
Harald Weltefbd4f732012-05-06 23:29:42 +0200112
113handle_info(Info, State, LoopDat) ->
114 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
115 {next_state, State, LoopDat}.
116
117
118%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
119% STATE "as_down"
120%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
121
122as_down(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
123 spec_name = indication, parameters = _Params}, LoopDat) ->
124 % One ASP transitions into ASP-INACTIVE
125 next_state(as_inactive, LoopDat);
126
127as_down(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_DOWN',
128 spec_name = indication, parameters = _Params}, LoopDat) ->
129 % ignore
130 next_state(as_down, LoopDat).
131
132
133%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
134% STATE "as_inactive"
135%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
136
137as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_DOWN',
138 spec_name = indication, parameters = AsPid}, LoopDat) ->
139 % One ASP transitions into ASP-DOWN
140 % FIXME: check if there are any other ASP != DOWN, if yes -> as_inactive
141 case check_any_other_asp_not_down(LoopDat, AsPid) of
142 true ->
143 next_state(as_inactive, LoopDat);
144 false ->
145 next_state(as_down, LoopDat)
146 end;
147
148as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
149 spec_name = indication, parameters = Params}, LoopDat) ->
150 % One ASP transitions to ASP-ACTIVE
151 next_state(as_active, LoopDat);
152
153as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
154 spec_name = indication, parameters = _Params}, LoopDat) ->
155 % ignore
156 next_state(as_inactive, LoopDat).
157
158
159%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
160% STATE "as_active"
161%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
162
163as_active(#primitive{subsystem = 'ASPAS', gen_name = InactDown,
164 spec_name = indication, parameters = AspPid}, LoopDat) when
165 InactDown == 'ASP_DOWN'; InactDown == 'ASP_INACTIVE' ->
166 % One ASP transitions to ASP-INACTIVE
167 % check if there are other ASP in active, if yes -> as_active
168 case check_any_other_asp_in_active(LoopDat, AspPid) of
169 true ->
170 next_state(as_active, LoopDat);
171 false ->
172 {ok, Tr} = timer:apply_after(?T_R_TIMEOUT, gen_fsm, send_event,
173 [self(), {timer_expired, t_r}]),
174 next_state(as_pending, LoopDat#as_state{t_r = Tr})
175 end;
176
177as_active(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
178 spec_name = indication, parameters = _Params}, LoopDat) ->
179 % ignore
180 next_state(as_active, LoopDat).
181
182
183%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
184% STATE "as_pending"
185%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
186
187as_pending(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
188 spec_name = indication}, LoopDat) ->
189 % One ASP transitions into ASP-ACTIVE
190 timer:cancel(LoopDat#as_state.t_r),
191 next_state(as_active, LoopDat);
192
193as_pending(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
194 spec_name = indication, parameters = _Params}, LoopDat) ->
195 % ignore
196 next_state(as_pending, LoopDat);
197
198% FIXME: do we need to re-check as_pending state if we get ASP_DOWN of the last
199% inactive ASP ?
Harald Welte312a1eb2012-05-09 00:02:59 +0200200as_pending(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_DOWN',
201 spec_name = indication, parameters = _Params}, LoopDat) ->
202 next_state(as_pending, LoopDat);
Harald Weltefbd4f732012-05-06 23:29:42 +0200203
204as_pending({timer_expired, t_r}, LoopDat) ->
205 % check if there is at least one ASP in ASP-INACTIVE -> AS-INACTIVE
206 case check_any_other_asp_in_inactive(LoopDat, undefined) of
207 true ->
208 next_state(as_inactive, LoopDat);
209 false ->
210 next_state(as_down, LoopDat)
211 end.
212
213%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
214% helper functions
215%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
216
217next_state(NewState, LoopDat) ->
218 %FIXME Module:as_state_change(NewState, LoopDat#as_state.ext_state),
219 {next_state, NewState, LoopDat}.
220
221%create_asp(LoopDatIn = #as_state{asp_module = {AspModule, AspModuleArgs},
222% asp_list = AspListIn}) ->
223% Args = [AspModule, AspModuleArgs, UserFun, UserFunArgs, SctpPid],
224% {ok, AspPid} = gen_fsm:start_link(xua_asp_fsm, Args, [{debug, [trace]}]),
225% {AspPid, LoopDatIn#{asp_list = [AspPid|AspListIn]}}.
226
227
228
229check_any_other_asp_in_inactive(LoopDat, AspPid) ->
230 check_any_other_asp_in_state('ASP_INACTIVE', LoopDat, AspPid).
231
232check_any_other_asp_in_active(LoopDat, AspPid) ->
233 check_any_other_asp_in_state('ASP_ACTIVE', LoopDat, AspPid).
234
235check_any_other_asp_not_down(LoopDat, AspPid) ->
236 ListWithoutMe = lists:delete(AspPid, LoopDat#as_state.asp_list),
237 StateList = build_asp_state_list(ListWithoutMe),
Harald Welte7c3ec172012-05-08 23:36:49 +0200238 not lists:all(fun(E) -> E == 'ASP_DOWN' end, StateList).
Harald Weltefbd4f732012-05-06 23:29:42 +0200239
240check_any_other_asp_in_state(State, LoopDat, AspPid) ->
241 ListWithoutMe = lists:delete(AspPid, LoopDat#as_state.asp_list),
242 StateList = build_asp_state_list(ListWithoutMe),
243 lists:member(State, StateList).
244
245build_asp_state_list(ListOfPids) ->
Harald Welte312a1eb2012-05-09 00:02:59 +0200246 [xua_asp_fsm:get_state(X) || X <- ListOfPids].