blob: 138797f2ccc1d44375577ff3ee1e3a7fa721db5a [file] [log] [blame]
Harald Welteb6689882012-01-16 16:00:45 +01001% RFC 4165 MTP2 P2P Adaption Layer coding / decoding
2
3% (C) 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 Welteb6689882012-01-16 16:00:45 +010033
34-module(m2pa_codec).
35-author('Harald Welte <laforge@gnumonks.org>').
36-include("m2pa.hrl").
37-include("mtp3.hrl").
38
39-export([parse_msg/1, encode_msg/1]).
40
41-compile({parse_transform, exprecs}).
42-export_records([m2pa_msg]).
43
44parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, Len, Remain) ->
45 <<State:32/big, Filler/binary>> = Remain,
46 Ret = [{link_state, State}],
47 if
48 byte_size(Filler) > 0 ->
49 {undefined, [{filler, Filler}|Ret]};
50 true ->
51 {undefined, Ret}
52 end;
Harald Weltef14ef9f2012-01-16 22:20:35 +010053parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, 16, <<>>) ->
Harald Welteae479582012-01-19 23:17:50 +010054 {undefined, []};
Harald Welteb6689882012-01-16 16:00:45 +010055parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Len, RemainIn) ->
Harald Welte958c6442012-01-16 21:40:22 +010056 <<Pri:1, _:7, Mtp3Bin/binary>> = RemainIn,
57 Mtp3 = mtp3_codec:parse_mtp3_msg(Mtp3Bin),
Harald Welteb6689882012-01-16 16:00:45 +010058 {Mtp3, []}.
59
60parse_msg(DataBin) when is_binary(DataBin) ->
61 <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, AllRemain/binary>> = DataBin,
62 <<_:8, BSN:24/big, _:8, FSN:24/big, Remain/binary>> = AllRemain,
63 {Mtp3, Params} = parse_m2pa_msgt(MsgClass, MsgType, MsgLen, Remain),
64 {ok, #m2pa_msg{msg_class = MsgClass, msg_type = MsgType,
65 fwd_seq_nr = FSN, back_seq_nr = BSN,
66 mtp3 = Mtp3, parameters = Params}}.
67
Harald Welteae479582012-01-19 23:17:50 +010068encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, undefined, _Params) ->
Harald Weltef14ef9f2012-01-16 22:20:35 +010069 <<>>;
Harald Welte958c6442012-01-16 21:40:22 +010070encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3, _Params) when is_binary(Mtp3) ->
Harald Welteeb8a1c12012-01-16 21:56:33 +010071 <<0:1, 0:7, Mtp3/binary>>;
Harald Welte958c6442012-01-16 21:40:22 +010072encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3, Params) when is_record(Mtp3, mtp3_msg) ->
73 Mtp3bin = mtp3_codec:encode_mtp3_msg(Mtp3),
74 encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3bin, Params);
Harald Welteb6689882012-01-16 16:00:45 +010075encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, _, Params) ->
76 State = proplists:get_value(link_state, Params),
77 % FIXME: filler
78 Filler = <<>>,
79 <<State:32/big, Filler/binary>>.
80
81
82encode_msg(Msg) when is_record(Msg, m2pa_msg) ->
83 #m2pa_msg{msg_class = MsgClass, msg_type = MsgType, fwd_seq_nr = FSN,
84 back_seq_nr = BSN, mtp3 = Mtp3, parameters = Params} = Msg,
85 Payload = encode_m2pa_msgt(MsgClass, MsgType, Mtp3, Params),
86 MsgLen = byte_size(Payload) + 16,
87 <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, 0:8, BSN:24/big, 0:8, FSN:24/big, Payload/binary>>.