blob: a6603dfede418edd9acee2a7e13b827a044576ac [file] [log] [blame]
Harald Welte84facd72012-01-17 10:11:31 +01001% SCCP SUA ASP xua_asp_fsm callback 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/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
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.
Harald Welte84facd72012-01-17 10:11:31 +010033
34-module(sua_asp).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behaviour(xua_asp_fsm).
37
38-include("osmo_util.hrl").
39-include("m3ua.hrl").
40-include("sua.hrl").
Harald Welte92e783d2012-04-01 19:52:01 +020041-include("xua.hrl").
Harald Welte84facd72012-01-17 10:11:31 +010042
43-export([init/1]).
44
45-export([gen_xua_msg/3, asp_down/3, asp_inactive/3, asp_active/3]).
46
47init([]) ->
48 {ok, we_have_no_state}.
49
50gen_xua_msg(MsgClass, MsgType, Params) ->
Harald Welte92e783d2012-04-01 19:52:01 +020051 #xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params}.
Harald Welte84facd72012-01-17 10:11:31 +010052
Harald Welte92e783d2012-04-01 19:52:01 +020053asp_down(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
Harald Welte84facd72012-01-17 10:11:31 +010054 LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
55 % convert from SUA to xua_msg and call into master module
56 xua_asp_fsm:asp_down({xua_msg, MsgClass, MsgType}, Mld);
Harald Welte92e783d2012-04-01 19:52:01 +020057asp_down(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
Harald Welte84facd72012-01-17 10:11:31 +010058 rx_sua(SuaMsg, asp_down, Mld).
59
Harald Welte92e783d2012-04-01 19:52:01 +020060asp_inactive(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
Harald Welte84facd72012-01-17 10:11:31 +010061 LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
62 % convert from SUA to xua_msg and call into master module
63 xua_asp_fsm:asp_inactive({xua_msg, MsgClass, MsgType}, Mld);
Harald Welte92e783d2012-04-01 19:52:01 +020064asp_inactive(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
Harald Welte84facd72012-01-17 10:11:31 +010065 rx_sua(SuaMsg, asp_inactive, Mld).
66
Harald Welte92e783d2012-04-01 19:52:01 +020067asp_active(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
Harald Welte84facd72012-01-17 10:11:31 +010068 LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
69 % convert from SUA to xua_msg and call into master module
70 xua_asp_fsm:asp_active({xua_msg, MsgClass, MsgType}, Mld);
Harald Welte92e783d2012-04-01 19:52:01 +020071asp_active(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
Harald Welte84facd72012-01-17 10:11:31 +010072 rx_sua(SuaMsg, asp_active, Mld).
73
74
75
Harald Welte92e783d2012-04-01 19:52:01 +020076rx_sua(Msg = #xua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
Harald Welte84facd72012-01-17 10:11:31 +010077 msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
78 % Send BEAT_ACK using the same payload as the BEAT msg
Harald Welte92e783d2012-04-01 19:52:01 +020079 xua_asp_fsm:send_sctp_to_peer(LoopDat, Msg#xua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
Harald Welte84facd72012-01-17 10:11:31 +010080 {next_state, State, LoopDat};
81
Harald Welte92e783d2012-04-01 19:52:01 +020082%rx_sua(Msg = #xua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
Harald Welte84facd72012-01-17 10:11:31 +010083 %msg_type = MsgType, payload = Params}, State, LoopDat) ->
84 % transform to classic MTP primitive and send up to the user
85 %Mtp = map_ssnm_to_mtp_prim(MsgType),
86 %send_prim_to_user(LoopDat, Mtp),
87 %{next_state, State, LoopDat};
88
Harald Welte92e783d2012-04-01 19:52:01 +020089rx_sua(Msg = #xua_msg{}, State, LoopDat) ->
Harald Welte84facd72012-01-17 10:11:31 +010090 io:format("SUA Unknown messge ~p in state ~p~n", [Msg, State]),
91 {next_state, State, LoopDat}.