blob: 974ffd8a97ca21939acf6857a0f446e4287e808e [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/>.
19
20-module(m2pa_codec).
21-author('Harald Welte <laforge@gnumonks.org>').
22-include("m2pa.hrl").
23-include("mtp3.hrl").
24
25-export([parse_msg/1, encode_msg/1]).
26
27-compile({parse_transform, exprecs}).
28-export_records([m2pa_msg]).
29
30parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, Len, Remain) ->
31 <<State:32/big, Filler/binary>> = Remain,
32 Ret = [{link_state, State}],
33 if
34 byte_size(Filler) > 0 ->
35 {undefined, [{filler, Filler}|Ret]};
36 true ->
37 {undefined, Ret}
38 end;
39parse_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Len, RemainIn) ->
Harald Welte958c6442012-01-16 21:40:22 +010040 <<Pri:1, _:7, Mtp3Bin/binary>> = RemainIn,
41 Mtp3 = mtp3_codec:parse_mtp3_msg(Mtp3Bin),
Harald Welteb6689882012-01-16 16:00:45 +010042 {Mtp3, []}.
43
44parse_msg(DataBin) when is_binary(DataBin) ->
45 <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, AllRemain/binary>> = DataBin,
46 <<_:8, BSN:24/big, _:8, FSN:24/big, Remain/binary>> = AllRemain,
47 {Mtp3, Params} = parse_m2pa_msgt(MsgClass, MsgType, MsgLen, Remain),
48 {ok, #m2pa_msg{msg_class = MsgClass, msg_type = MsgType,
49 fwd_seq_nr = FSN, back_seq_nr = BSN,
50 mtp3 = Mtp3, parameters = Params}}.
51
Harald Welte958c6442012-01-16 21:40:22 +010052encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3, _Params) when is_binary(Mtp3) ->
Harald Welteeb8a1c12012-01-16 21:56:33 +010053 <<0:1, 0:7, Mtp3/binary>>;
Harald Welte958c6442012-01-16 21:40:22 +010054encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3, Params) when is_record(Mtp3, mtp3_msg) ->
55 Mtp3bin = mtp3_codec:encode_mtp3_msg(Mtp3),
56 encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_USER, Mtp3bin, Params);
Harald Welteb6689882012-01-16 16:00:45 +010057encode_m2pa_msgt(?M2PA_CLASS_M2PA, ?M2PA_TYPE_LINK, _, Params) ->
58 State = proplists:get_value(link_state, Params),
59 % FIXME: filler
60 Filler = <<>>,
61 <<State:32/big, Filler/binary>>.
62
63
64encode_msg(Msg) when is_record(Msg, m2pa_msg) ->
65 #m2pa_msg{msg_class = MsgClass, msg_type = MsgType, fwd_seq_nr = FSN,
66 back_seq_nr = BSN, mtp3 = Mtp3, parameters = Params} = Msg,
67 Payload = encode_m2pa_msgt(MsgClass, MsgType, Mtp3, Params),
68 MsgLen = byte_size(Payload) + 16,
69 <<1:8, 0:8, MsgClass:8, MsgType:8, MsgLen:32/big, 0:8, BSN:24/big, 0:8, FSN:24/big, Payload/binary>>.