blob: 27ceba9b2c57147536ac7f8fa63660aba2a13fc4 [file] [log] [blame]
Harald Welte0c40c622019-08-22 17:35:10 +02001% ip.access IPA CCM protocol
2
3% (C) 2019 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 General Public License as published by
9% the Free Software Foundation; either version 2 of the License, or
10% (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.
Harald Welte0c40c622019-08-22 17:35:10 +020016
17-module(ipa_proto_ccm).
18-author('Harald Welte <laforge@gnumonks.org>').
19
20-export([decode/1, encode/1]).
21
22-define(TESTMSG, <<5,0,7,8,48,47,48,47,48,0,0,19,7,48,48,58,48,48,58,48,48,58,48,48,58,48,48,58,
23 48,48,0,0,19,2,48,48,58,48,48,58,48,48,58,48,48,58,48,48,58,48,48,0,0,19,3,
24 48,48,58,48,48,58,48,48,58,48,48,58,48,48,58,48,48,0,0,19,4,48,48,58,48,48,
25 58,48,48,58,48,48,58,48,48,58,48,48,0,0,24,5,111,115,109,111,45,109,115,99,
26 45,49,46,51,46,49,46,49,49,45,52,50,55,50,0,0,23,1,77,83,67,45,48,48,45,48,
27 48,45,48,48,45,48,48,45,48,48,45,48,48,0,0,23,0,77,83,67,45,48,48,45,48,48,
28 45,48,48,45,48,48,45,48,48,45,48,48,0>>).
29
30decode_msgt(0) -> ping;
31decode_msgt(1) -> pong;
32decode_msgt(4) -> id_req;
33decode_msgt(5) -> id_resp;
34decode_msgt(6) -> id_ack;
35decode_msgt(7) -> id_nack;
36decode_msgt(8) -> proxy_req;
37decode_msgt(9) -> proxy_ack;
38decode_msgt(10) -> proxy_nack;
39decode_msgt(Int) when is_integer(Int) -> Int.
40
41encode_msgt(ping) -> 0;
42encode_msgt(pong) -> 1;
43encode_msgt(id_req) -> 4;
44encode_msgt(id_resp) -> 5;
45encode_msgt(id_ack) -> 6;
46encode_msgt(id_nack) -> 7;
47encode_msgt(proxy_req) -> 8;
48encode_msgt(proxy_ack) -> 9;
49encode_msgt(proxy_nack) -> 10;
50encode_msgt(Int) when is_integer(Int) -> Int.
51
52decode_idtag(0) -> serial_nr;
53decode_idtag(1) -> unit_name;
54decode_idtag(2) -> location;
55decode_idtag(3) -> unit_type;
56decode_idtag(4) -> equip_vers;
57decode_idtag(5) -> sw_version;
58decode_idtag(6) -> ip_address;
59decode_idtag(7) -> mac_address;
60decode_idtag(8) -> unit_id;
61decode_idtag(Int) when is_integer(Int) -> Int.
62
63encode_idtag(serial_nr) -> 0;
64encode_idtag(unit_name) -> 1;
65encode_idtag(location) -> 2;
66encode_idtag(unit_type) -> 3;
67encode_idtag(equip_vers) -> 4;
68encode_idtag(sw_version) -> 5;
69encode_idtag(ip_address) -> 6;
70encode_idtag(mac_address) -> 7;
71encode_idtag(unit_id) -> 8;
72encode_idtag(Int) when is_integer(Int) -> Int.
73
74decode(Bin) when is_binary(Bin) ->
75 <<MsgType:8, IeList/binary>> = Bin,
76 {decode_msgt(MsgType), decode_ies(IeList, [])}.
77
78decode_ies(<<>>, IeList) when is_list(IeList) ->
79 IeList;
80decode_ies(<<1:8, IdTag:8, Remain/binary>>, IeList) when is_list(IeList) ->
81 decode_ies(Remain, IeList ++ [{id, IdTag}]);
82decode_ies(<<0:8, Len:8, TypeValue:Len/binary, Remain/binary>>, IeList) when is_list(IeList) ->
83 <<Type:8, Value/binary>> = TypeValue,
84 ValueList = binary_to_list(Value),
85 case lists:last(ValueList) of
86 0 -> ValueStripped = lists:droplast(ValueList);
87 _ -> ValueStripped = ValueList
88 end,
89 decode_ies(Remain, IeList ++ [{string, decode_idtag(Type), ValueStripped}]).
90
91
92encode_ie({id, IdTag}) ->
93 <<1:8, IdTag:8>>;
94encode_ie({string, Type, Value}) ->
95 case lists:last(Value) of
96 0 -> ValueTerminated = Value;
97 _ -> ValueTerminated = lists:append(Value, [0])
98 end,
99 ValueBin = list_to_binary(ValueTerminated),
100 Type2 = encode_idtag(Type),
101 TypeValue = <<Type2:8, ValueBin/binary>>,
102 Len = byte_size(TypeValue),
103 <<0:8, Len:8, TypeValue/binary>>.
104
105encode_ies(IeList) when is_list(IeList) ->
106 encode_ies(IeList, <<>>).
107encode_ies([], Bin) -> Bin;
108encode_ies([Head|Tail], Bin) ->
109 IeBin = encode_ie(Head),
110 encode_ies(Tail, <<Bin/binary, IeBin/binary>>).
111
112encode({MsgType, IeList}) ->
113 MsgtInt = encode_msgt(MsgType),
114 IesBin = encode_ies(IeList),
115 <<MsgtInt:8, IesBin/binary>>.