From 231ae0b993f48b670a5c38e78e4ed158b720072b Mon Sep 17 00:00:00 2001 From: Harald Welte Date: Sun, 1 Apr 2012 20:13:23 +0200 Subject: M2UA Codec: Use generic xUA codec instead --- include/m2ua.hrl | 1 + src/m2ua_codec.erl | 72 +++-------------------------------------------- src/m3ua_core.erl | 1 + test/isup_codec_tests.erl | 9 +++--- test/m2ua_codec_tests.erl | 9 ++++-- 5 files changed, 17 insertions(+), 75 deletions(-) diff --git a/include/m2ua.hrl b/include/m2ua.hrl index ce9d9e5..371ef46 100644 --- a/include/m2ua.hrl +++ b/include/m2ua.hrl @@ -1,3 +1,4 @@ + -define(M2UA_PPID, 2). -define(M2UA_PORT, 2904). diff --git a/src/m2ua_codec.erl b/src/m2ua_codec.erl index 32bec00..437b3e8 100644 --- a/src/m2ua_codec.erl +++ b/src/m2ua_codec.erl @@ -19,79 +19,15 @@ -module(m2ua_codec). -author('Harald Welte '). +-include("xua.hrl"). -include("m2ua.hrl"). -export([parse_m2ua_msg/1, encode_m2ua_msg/1]). --compile({parse_transform, exprecs}). --export_records([m2ua_msg]). - -% compute the number of pad bits required after a binary parameter -get_num_pad_bytes(BinLenBytes) -> - case BinLenBytes rem 4 of - 0 -> 0; - Val -> 4 - Val - end. - -% parse a binary chunk of options into an options proplist -parse_m2ua_opts(<<>>, OptList) when is_list(OptList) -> - OptList; -parse_m2ua_opts(OptBin, OptList) when is_list(OptList) -> - <> = OptBin, - Length = LengthIncHdr - 4, - PadLength = get_num_pad_bytes(Length), - %io:format("Tag ~w, LenInHdr ~w, Len ~w, PadLen ~w, Remain ~w(~p)~n", - % [Tag, LengthIncHdr, Length, PadLength, byte_size(Remain), Remain]), - <> = Remain, - % this is ridiculous, we cannot use "<>" as the last part would not match an - % empty binary <<>> anymore. Without the "0:PadLengh" this works - % perfectly fine. Now we need some complicated construct and check if - % the resulting list would be empty :(( - if - byte_size(PadNextOpts) > PadLength -> - <<0:PadLength/integer-unit:8, NextOpts/binary>> = PadNextOpts; - true -> - NextOpts = <<>> - end, - NewOpt = {Tag, {Length, Value}}, - parse_m2ua_opts(NextOpts, OptList ++ [NewOpt]). - -% parse a single M2UA message -parse_m2ua_msgt(_, _, _, Remain) -> - parse_m2ua_opts(Remain, []). - % parse a M2UA message binary into a record parse_m2ua_msg(DataBin) when is_binary(DataBin) -> - <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, Remain/binary>> = DataBin, - Parsed = parse_m2ua_msgt(MsgClass, MsgType, MsgLen, Remain), - {ok, #m2ua_msg{msg_class = MsgClass, msg_type = MsgType, parameters = Parsed}}. - - - -% encode a single option -encode_m2ua_opt({OptNum, {DataBinLen, DataBin}}) when is_integer(OptNum) -> - LengthIncHdr = DataBinLen + 4, - PadLength = get_num_pad_bytes(DataBinLen), - case PadLength of - 0 -> <>; - _ -> <> - end. - -% encode a list of options -encode_m2ua_opts([], OptEnc) -> - OptEnc; -encode_m2ua_opts([CurOpt|OptPropList], OptEnc) -> - CurOptEnc = encode_m2ua_opt(CurOpt), - encode_m2ua_opts(OptPropList, <>). - - -% encode a particular message type -encode_m2ua_msgt(MsgClass, MsgType, Params) -> - OptBin = encode_m2ua_opts(Params, <<>>), - MsgLenIncHdr = 8 + byte_size(OptBin), - <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLenIncHdr:32/big, OptBin/binary>>. + xua_codec:parse_msg(DataBin). % encode a message from record to binary -encode_m2ua_msg(#m2ua_msg{msg_class = MsgClass, msg_type = MsgType, parameters = Params}) -> - encode_m2ua_msgt(MsgClass, MsgType, Params). +encode_m2ua_msg(Msg) when is_record(Msg, xua_msg) -> + xua_codec:encode_msg(Msg). diff --git a/src/m3ua_core.erl b/src/m3ua_core.erl index 3167c81..ef443ae 100644 --- a/src/m3ua_core.erl +++ b/src/m3ua_core.erl @@ -67,6 +67,7 @@ start_link(InitOpts) -> gen_fsm:start_link(?MODULE, InitOpts, [{debug, [trace]}]). reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sctp_sock = Sock}) -> + timer:sleep(1*1000), io:format("SCTP Reconnect ~p:~p~n", [Ip, Port]), InitMsg = #sctp_initmsg{num_ostreams = 2, max_instreams = 2}, case gen_sctp:connect(Sock, Ip, Port, [{active, once}, {reuseaddr, true}, diff --git a/test/isup_codec_tests.erl b/test/isup_codec_tests.erl index 0b2d49a..2fd421f 100644 --- a/test/isup_codec_tests.erl +++ b/test/isup_codec_tests.erl @@ -4,6 +4,7 @@ -include_lib("eunit/include/eunit.hrl"). -include("isup.hrl"). +-include("xua.hrl"). -include("m2ua.hrl"). -include("mtp3.hrl"). @@ -44,12 +45,12 @@ pcap_parse_test() -> end. pcap_cb(sctp, _From, _Path, 2, DataBin) -> - {ok, M2ua} = m2ua_codec:parse_m2ua_msg(DataBin), + M2ua = m2ua_codec:parse_m2ua_msg(DataBin), handle_m2ua(M2ua). -handle_m2ua(#m2ua_msg{msg_class = ?M2UA_MSGC_MAUP, - msg_type = ?M2UA_MAUP_MSGT_DATA, - parameters = Params}) -> +handle_m2ua(#xua_msg{msg_class = ?M2UA_MSGC_MAUP, + msg_type = ?M2UA_MAUP_MSGT_DATA, + payload = Params}) -> {_Len, M2uaPayload} = proplists:get_value(16#300, Params), Mtp3 = mtp3_codec:parse_mtp3_msg(M2uaPayload), handle_mtp3(Mtp3); diff --git a/test/m2ua_codec_tests.erl b/test/m2ua_codec_tests.erl index 33d807d..3e09c7b 100644 --- a/test/m2ua_codec_tests.erl +++ b/test/m2ua_codec_tests.erl @@ -3,6 +3,7 @@ -include_lib("eunit/include/eunit.hrl"). +-include("xua.hrl"). -include("m2ua.hrl"). -define(M2UA_MSG_BIN, <<1,0,6,1,0,0,0,124,0,1,0,8,0,0,0,0,3,0,0,105,131,92, @@ -11,9 +12,11 @@ 81,1,2,200,107,42,40,40,6,7,0,17,134,5,1,1,1,160, 29,97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162, 3,2,1,0,163,5,161,3,2,1,0,108,13,163,11,2,1,64,2,1,8,48,3,10,1,0,0,0,0>>). --define(M2UA_MSG_DEC, {m2ua_msg,6,1,[{1,{4,<<0,0,0,0>>}},{768,{101,<<131,92,64,0,192,9,0,3,13,24,10,18,7,0,18,4,83,132,9,0,23,11,18,6,0,18,4,68,119,88,16,70,35,67,100,65,73,4,81,1,2,200,107,42,40,40,6,7,0,17,134,5,1,1,1,160,29,97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0,108,13,163,11,2,1,64,2,1,8,48,3,10,1,0>>}}]}). +-define(M2UA_MSG_DEC, {xua_msg,1,6,1,[{1,{4,<<0,0,0,0>>}},{768,{101,<<131,92,64,0,192,9,0,3,13,24,10,18,7,0,18,4,83,132,9,0,23,11,18,6,0,18,4,68,119,88,16,70,35,67,100,65,73,4,81,1,2,200,107,42,40,40,6,7,0,17,134,5,1,1,1,160,29,97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0,108,13,163,11,2,1,64,2,1,8,48,3,10,1,0>>}}]}). parse_test() -> - ?assertEqual({ok, ?M2UA_MSG_DEC}, m2ua_codec:parse_m2ua_msg(?M2UA_MSG_BIN)). + ?assertEqual(?M2UA_MSG_DEC, m2ua_codec:parse_m2ua_msg(?M2UA_MSG_BIN)), + ?assertEqual(?M2UA_MSG_DEC, xua_codec:parse_msg(?M2UA_MSG_BIN)). encode_test() -> - ?assertEqual(?M2UA_MSG_BIN, m2ua_codec:encode_m2ua_msg(?M2UA_MSG_DEC)). + ?assertEqual(?M2UA_MSG_BIN, m2ua_codec:encode_m2ua_msg(?M2UA_MSG_DEC)), + ?assertEqual(?M2UA_MSG_BIN, xua_codec:encode_msg(?M2UA_MSG_DEC)). -- cgit v1.2.3