summaryrefslogtreecommitdiffstats
path: root/src/sua_asp.erl
diff options
context:
space:
mode:
authorHarald Welte <laforge@gnumonks.org>2012-04-01 19:52:01 +0200
committerHarald Welte <laforge@gnumonks.org>2012-04-01 19:54:20 +0200
commit92e783d1098e99161401ab08cccd3a08356749cd (patch)
tree514413efb1a8bb953169f1d6d8c57e3280a03eb7 /src/sua_asp.erl
parent7aff8fb62be1422016ec92df5d1cbec0c738b75c (diff)
rename sua_codec to generic xua_codec
SUA/M3UA/M2UA/M2PA actaully all uses almost the same message format, so it makes sense to write one generic xua_codec and derive from that. The current SUA implementation didn't actually contain anything SUA specific, so we can just rename it and use xua_codec directly from the users.
Diffstat (limited to 'src/sua_asp.erl')
-rw-r--r--src/sua_asp.erl23
1 files changed, 12 insertions, 11 deletions
diff --git a/src/sua_asp.erl b/src/sua_asp.erl
index 79a4fd3..d75d688 100644
--- a/src/sua_asp.erl
+++ b/src/sua_asp.erl
@@ -24,6 +24,7 @@
-include("osmo_util.hrl").
-include("m3ua.hrl").
-include("sua.hrl").
+-include("xua.hrl").
-export([init/1]).
@@ -33,44 +34,44 @@ init([]) ->
{ok, we_have_no_state}.
gen_xua_msg(MsgClass, MsgType, Params) ->
- #sua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params}.
+ #xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType, payload = Params}.
-asp_down(#sua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+asp_down(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
% convert from SUA to xua_msg and call into master module
xua_asp_fsm:asp_down({xua_msg, MsgClass, MsgType}, Mld);
-asp_down(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, sua_msg) ->
+asp_down(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
rx_sua(SuaMsg, asp_down, Mld).
-asp_inactive(#sua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+asp_inactive(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
% convert from SUA to xua_msg and call into master module
xua_asp_fsm:asp_inactive({xua_msg, MsgClass, MsgType}, Mld);
-asp_inactive(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, sua_msg) ->
+asp_inactive(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
rx_sua(SuaMsg, asp_inactive, Mld).
-asp_active(#sua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
+asp_active(#xua_msg{version = 1, msg_class = MsgClass, msg_type = MsgType},
LoopDat, Mld) when MsgClass == ?M3UA_MSGC_ASPSM; MsgClass == ?M3UA_MSGC_ASPTM ->
% convert from SUA to xua_msg and call into master module
xua_asp_fsm:asp_active({xua_msg, MsgClass, MsgType}, Mld);
-asp_active(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, sua_msg) ->
+asp_active(SuaMsg, LoopDat, Mld) when is_record(SuaMsg, xua_msg) ->
rx_sua(SuaMsg, asp_active, Mld).
-rx_sua(Msg = #sua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
+rx_sua(Msg = #xua_msg{version = 1, msg_class = ?M3UA_MSGC_ASPSM,
msg_type = ?M3UA_MSGT_ASPSM_BEAT}, State, LoopDat) ->
% Send BEAT_ACK using the same payload as the BEAT msg
- xua_asp_fsm:send_sctp_to_peer(LoopDat, Msg#sua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
+ xua_asp_fsm:send_sctp_to_peer(LoopDat, Msg#xua_msg{msg_type = ?M3UA_MSGT_ASPSM_BEAT_ACK}),
{next_state, State, LoopDat};
-%rx_sua(Msg = #sua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
+%rx_sua(Msg = #xua_msg{version = 1, msg_class = ?M3UA_MSGC_SSNM,
%msg_type = MsgType, payload = Params}, State, LoopDat) ->
% transform to classic MTP primitive and send up to the user
%Mtp = map_ssnm_to_mtp_prim(MsgType),
%send_prim_to_user(LoopDat, Mtp),
%{next_state, State, LoopDat};
-rx_sua(Msg = #sua_msg{}, State, LoopDat) ->
+rx_sua(Msg = #xua_msg{}, State, LoopDat) ->
io:format("SUA Unknown messge ~p in state ~p~n", [Msg, State]),
{next_state, State, LoopDat}.