blob: 386c51a8a0d32c56c920ba7893aaceab9f5e503a [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
42-export([init/1, terminate/3, code_change/4, handle_event/3, handle_info/3]).
43
44% states in this FSM
45-export([as_down/2, as_inactive/2, as_active/2, as_pending/2]).
46
47% Timeouts in milliseconds
48-define(T_R_TIMEOUT, 2*60*100).
49
50-record(as_state, {
51 role,
52 t_r,
53 asp_list
54 }).
55
56%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
57% gen_fsm callbacks
58%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
59
60init([]) ->
61 AsState = #as_state{asp_list = [],
62 role = sg},
63 {ok, as_down, AsState}.
64
65terminate(Reason, State, _LoopDat) ->
66 io:format("Terminating ~p in State ~p (Reason: ~p)~n",
67 [?MODULE, State, Reason]),
68 ok.
69
70code_change(_OldVsn, StateName, LoopDat, _Extra) ->
71 {ok, StateName, LoopDat}.
72
73handle_event(Event, State, LoopDat) ->
74 io:format("Unknown Event ~p in state ~p~n", [Event, State]),
75 {next_state, State, LoopDat}.
76
77handle_info({'EXIT', Pid, Reason}, State, LoopDat) ->
78 io:format("EXIT from Process ~p (~p), cleaning up ASP list~n",
79 [Pid, Reason]),
80 % FIXME: send fake ASP-DOWN event about ASP to self
81 {next_state, State, LoopDat};
82
83handle_info(Info, State, LoopDat) ->
84 io:format("Unknown Info ~p in state ~p~n", [Info, State]),
85 {next_state, State, LoopDat}.
86
87
88%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
89% STATE "as_down"
90%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
91
92as_down(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
93 spec_name = indication, parameters = _Params}, LoopDat) ->
94 % One ASP transitions into ASP-INACTIVE
95 next_state(as_inactive, LoopDat);
96
97as_down(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_DOWN',
98 spec_name = indication, parameters = _Params}, LoopDat) ->
99 % ignore
100 next_state(as_down, LoopDat).
101
102
103%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
104% STATE "as_inactive"
105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
106
107as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_DOWN',
108 spec_name = indication, parameters = AsPid}, LoopDat) ->
109 % One ASP transitions into ASP-DOWN
110 % FIXME: check if there are any other ASP != DOWN, if yes -> as_inactive
111 case check_any_other_asp_not_down(LoopDat, AsPid) of
112 true ->
113 next_state(as_inactive, LoopDat);
114 false ->
115 next_state(as_down, LoopDat)
116 end;
117
118as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
119 spec_name = indication, parameters = Params}, LoopDat) ->
120 % One ASP transitions to ASP-ACTIVE
121 next_state(as_active, LoopDat);
122
123as_inactive(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
124 spec_name = indication, parameters = _Params}, LoopDat) ->
125 % ignore
126 next_state(as_inactive, LoopDat).
127
128
129%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
130% STATE "as_active"
131%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
132
133as_active(#primitive{subsystem = 'ASPAS', gen_name = InactDown,
134 spec_name = indication, parameters = AspPid}, LoopDat) when
135 InactDown == 'ASP_DOWN'; InactDown == 'ASP_INACTIVE' ->
136 % One ASP transitions to ASP-INACTIVE
137 % check if there are other ASP in active, if yes -> as_active
138 case check_any_other_asp_in_active(LoopDat, AspPid) of
139 true ->
140 next_state(as_active, LoopDat);
141 false ->
142 {ok, Tr} = timer:apply_after(?T_R_TIMEOUT, gen_fsm, send_event,
143 [self(), {timer_expired, t_r}]),
144 next_state(as_pending, LoopDat#as_state{t_r = Tr})
145 end;
146
147as_active(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
148 spec_name = indication, parameters = _Params}, LoopDat) ->
149 % ignore
150 next_state(as_active, LoopDat).
151
152
153%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
154% STATE "as_pending"
155%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
156
157as_pending(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_ACTIVE',
158 spec_name = indication}, LoopDat) ->
159 % One ASP transitions into ASP-ACTIVE
160 timer:cancel(LoopDat#as_state.t_r),
161 next_state(as_active, LoopDat);
162
163as_pending(#primitive{subsystem = 'ASPAS', gen_name = 'ASP_INACTIVE',
164 spec_name = indication, parameters = _Params}, LoopDat) ->
165 % ignore
166 next_state(as_pending, LoopDat);
167
168% FIXME: do we need to re-check as_pending state if we get ASP_DOWN of the last
169% inactive ASP ?
170
171as_pending({timer_expired, t_r}, LoopDat) ->
172 % check if there is at least one ASP in ASP-INACTIVE -> AS-INACTIVE
173 case check_any_other_asp_in_inactive(LoopDat, undefined) of
174 true ->
175 next_state(as_inactive, LoopDat);
176 false ->
177 next_state(as_down, LoopDat)
178 end.
179
180%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
181% helper functions
182%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
183
184next_state(NewState, LoopDat) ->
185 %FIXME Module:as_state_change(NewState, LoopDat#as_state.ext_state),
186 {next_state, NewState, LoopDat}.
187
188%create_asp(LoopDatIn = #as_state{asp_module = {AspModule, AspModuleArgs},
189% asp_list = AspListIn}) ->
190% Args = [AspModule, AspModuleArgs, UserFun, UserFunArgs, SctpPid],
191% {ok, AspPid} = gen_fsm:start_link(xua_asp_fsm, Args, [{debug, [trace]}]),
192% {AspPid, LoopDatIn#{asp_list = [AspPid|AspListIn]}}.
193
194
195
196check_any_other_asp_in_inactive(LoopDat, AspPid) ->
197 check_any_other_asp_in_state('ASP_INACTIVE', LoopDat, AspPid).
198
199check_any_other_asp_in_active(LoopDat, AspPid) ->
200 check_any_other_asp_in_state('ASP_ACTIVE', LoopDat, AspPid).
201
202check_any_other_asp_not_down(LoopDat, AspPid) ->
203 ListWithoutMe = lists:delete(AspPid, LoopDat#as_state.asp_list),
204 StateList = build_asp_state_list(ListWithoutMe),
205 not lists:all('ASP_DOWN', StateList).
206
207check_any_other_asp_in_state(State, LoopDat, AspPid) ->
208 ListWithoutMe = lists:delete(AspPid, LoopDat#as_state.asp_list),
209 StateList = build_asp_state_list(ListWithoutMe),
210 lists:member(State, StateList).
211
212build_asp_state_list(ListOfPids) ->
213 % FIXME
214 [].