blob: 61cf85e049e983d6376f77ada03e72f94fb7f8f0 [file] [log] [blame]
Harald Welte78474ae2011-02-07 20:48:41 +01001% GSM TS 08.08 / 3GPP TS 48.008 BSSMAP
2
3% (C) 2010 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(bssmap_codec).
21-author('Harald Welte <laforge@gnumonks.org>').
22-include("bssmap.hrl").
23
24-export([parse_bssmap_msg/1, encode_bssmap_msg/1]).
25
26parse_bssmap_msg(<<MsgType:8, Remain/binary>>) ->
27 parse_bssmap_msgt(MsgType, Remain).
28
29parse_bssmap_msgt(MsgType, Msg) when is_integer(MsgType), is_binary(Msg) ->
30 IeList = parse_ies(Msg, []),
31 {bssmap_msg, MsgType, IeList}.
32
33parse_ies(<<>>, ParsedIeList) ->
34 ParsedIeList;
35parse_ies(Msg, ParsedIeList) when is_binary(Msg) ->
36 CurIe = binary:first(Msg),
37 % Parse current IE and append it to list of Parsed IEs
38 case is_tv_ie(CurIe) of
39 true ->
40 Res = parse_ie_tv(CurIe, Msg);
41 false ->
42 Res = parse_ie(CurIe, Msg)
43 end,
44 {ok, BytesConsumed, ParsedIe} = Res,
45 {CurIe, Payload} = ParsedIe,
46 DecodedIe = decode_ie(CurIe, Payload),
47 ParsedIeList1 = ParsedIeList ++ [DecodedIe],
48 %ParsedIeList1 = ParsedIeList ++ [ParsedIe],
49 RemainMsg = binary:part(Msg, BytesConsumed, byte_size(Msg)-BytesConsumed),
50 parse_ies(RemainMsg, ParsedIeList1).
51
52% check if this element is of TV type
53is_tv_ie(T) when
54 T == ?BSSMAP_IE_NUMBER_OF_MSS;
55 T == ?BSSMAP_IE_PERIODICITY;
56 T == ?BSSMAP_IE_EXTD_RES_IND;
57 T == ?BSSMAP_IE_INTERF_BAND_TO_USE;
58 T == ?BSSMAP_IE_RR_CAUSE;
59 T == ?BSSMAP_IE_DLCI;
60 T == ?BSSMAP_IE_DOWNLINK_DTX_FLAG;
61 T == ?BSSMAP_IE_RESPONSE_RQST;
62 T == ?BSSMAP_IE_RES_IND_METHOD;
63 T == ?BSSMAP_IE_CM_INFO_T1;
64 T == ?BSSMAP_IE_CHOSEN_CHANNEL;
65 T == ?BSSMAP_IE_CIPH_RESP_MODE;
66 T == ?BSSMAP_IE_TRACE_TYPE;
67 T == ?BSSMAP_IE_TRACE_REFERENCE;
68 T == ?BSSMAP_IE_FORWARD_INDICATOR;
69 T == ?BSSMAP_IE_CHOSEN_ENCR_ALG;
70 T == ?BSSMAP_IE_CIRCUIT_POOL;
71 T == ?BSSMAP_IE_TIME_INDICATION;
72 T == ?BSSMAP_IE_CUR_CHAN_TYPE_1;
73 T == ?BSSMAP_IE_QUEUEING_IND;
74 T == ?BSSMAP_IE_SPEECH_VERSION;
75 T == ?BSSMAP_IE_ASS_REQUIREMENT;
76 T == ?BSSMAP_IE_EMLPP_PRIORITY;
77 T == ?BSSMAP_IE_CONFIG_EVO_INDI;
78 T == ?BSSMAP_IE_LSA_ACCESS_CTRL_SUPPR ->
79 true;
80is_tv_ie(_T) ->
81 false.
82
83% Parser for any non-TLV and non-TV IEs
84parse_ie(?BSSMAP_IE_CIRC_ID_CODE, Msg) ->
85 <<?BSSMAP_IE_CIRC_ID_CODE:8, Cic:16/big>> = Msg,
86 {ok, 3, {?BSSMAP_IE_CIRC_ID_CODE, Cic}};
87parse_ie(?BSSMAP_IE_CONN_REL_RQSTED, Msg) ->
88 <<?BSSMAP_IE_CONN_REL_RQSTED:8>> = Msg,
89 {ok, 1, {?BSSMAP_IE_CONN_REL_RQSTED, 1}};
90parse_ie(?BSSMAP_IE_RES_AVAIL, Msg) ->
91 <<?BSSMAP_IE_RES_AVAIL:8, ResAvail:8/binary>> = Msg,
92 {ok, 9, {?BSSMAP_IE_RES_AVAIL, ResAvail}};
93parse_ie(?BSSMAP_IE_TOT_RES_ACCESS, Msg) ->
94 <<?BSSMAP_IE_TOT_RES_ACCESS:8, ResAvail:4/binary>> = Msg,
95 {ok, 5, {?BSSMAP_IE_TOT_RES_ACCESS, ResAvail}};
96parse_ie(?BSSMAP_IE_TALKER_FLAG, Msg) ->
97 <<?BSSMAP_IE_TALKER_FLAG:8>> = Msg,
98 {ok, 1, {?BSSMAP_IE_TALKER_FLAG, 1}};
99% Default: Parser for TLV IE
100parse_ie(MsgType, Msg) ->
101 <<MsgType:8, Length:8, Value:Length/binary, _/binary>> = Msg,
102 {ok, 2+Length, {MsgType, Value}}.
103
104% Parser for simple Tag-Value IE
105parse_ie_tv(IeType, Msg) ->
106 <<IeType:8, Par:8>> = Msg,
107 {ok, 2, {IeType, Par}}.
108
109
110% FIXME
111encode_bssmap_msg(_) ->
112 ok.
113
114
115
116
117
118decode_ie(?BSSMAP_IE_CIRC_ID_CODE, <<Pcm:11, Ts:5>>) ->
119 {circuit_id, Pcm, Ts};
120decode_ie(?BSSMAP_IE_IMSI, Remain) ->
121 {imsi, bin_bcd2str(Remain)};
122decode_ie(?BSSMAP_IE_TMSI, <<Tmsi:32>>) ->
123 {tmsi, Tmsi};
124decode_ie(?BSSMAP_IE_L3_HDR_INFO, <<Pdisc:8, Tid:8>>) ->
125 {l3_hdr_info, Pdisc, Tid};
126decode_ie(?BSSMAP_IE_ENCR_INFO, <<Algos:8, Key/binary>>) ->
127 {encr_info, Algos, Key};
128decode_ie(?BSSMAP_IE_CHANNEL_TYPE, <<_:4, Spdi:4, RateType:8, Remain/binary>>) ->
129 {chan_type, Spdi, RateType, Remain};
130decode_ie(?BSSMAP_IE_EXTD_RES_IND, Ri) ->
131 <<_:6, Sm:1, Tarr:1>> = <<Ri>>,
132 {extended_ri, Sm, Tarr};
133decode_ie(?BSSMAP_IE_TOT_RES_ACCESS, <<NumFr:16/big, NumHr:16/big>>) ->
134 {tot_res_access, NumFr, NumHr};
135decode_ie(?BSSMAP_IE_CELL_ID, <<_Spare:4, Discr:4, Remain/binary>>) ->
136 {cell_id, decode_cid_ie(Discr, Remain)};
137decode_ie(?BSSMAP_IE_PRIORITY, <<_:1, Pci:1, Prio:4, Qa:1, Pvi:1>>) ->
138 {priority, Pci, Prio, Qa, Pvi};
139decode_ie(?BSSMAP_IE_CELL_ID_LIST, <<_Spare:4, Discr:4, Remain/binary>>) ->
140 {cell_id_list, decode_cid_list(Discr, Remain, [])};
141decode_ie(?BSSMAP_IE_DIAGNOSTIC, <<ErrPtr:8, _:4, BitPtr:4, MsgRecv/binary>>) ->
142 {diagnostic, ErrPtr, BitPtr, MsgRecv};
143decode_ie(?BSSMAP_IE_CHOSEN_CHANNEL, Int) ->
144 <<Mode:4, Chan:4>> = <<Int:8>>,
145 {chosen_channel, Mode, Chan};
146decode_ie(?BSSMAP_IE_MOBILE_IDENTITY, Data) ->
147 % FIXME
148 fixme;
149% Default: don't decode
150decode_ie(IeI, Data) ->
151 {IeI, Data}.
152
153decode_cid_ie(?CELL_ID_WHOLE_GLOBAL, Remain) ->
154 <<Mcc2:4, Mcc1:4, Mnc3:4, Mcc3:4, Mnc2:4, Mnc1:4, Lac:16/big, Ci:16/big>> = Remain,
155 [{mcc, [Mcc1, Mcc2, Mcc3]}, {mnc, [Mnc1, Mnc2, Mnc3]}, {lac, Lac}, {cid, Ci}];
156decode_cid_ie(?CELL_ID_LAC_AND_CI, Remain) ->
157 <<Lac:16/big, Ci:16/big>> = Remain,
158 [{lac, Lac}, {cid, Ci}];
159decode_cid_ie(?CELL_ID_CI, Remain) ->
160 <<Ci:16/big>> = Remain,
161 [{cid, Ci}];
162decode_cid_ie(?CELL_ID_NO_CELL, _Remain) ->
163 [];
164decode_cid_ie(?CELL_ID_UTRAN_PLMN_LAC_RNC, Remain) ->
165 <<Mcc2:4, Mcc1:4, Mnc3:4, Mcc3:4, Mnc2:4, Mnc1:4, Lac:16/big, Rnc:16/big>> = Remain,
166 [{mcc, [Mcc1, Mcc2, Mcc3]}, {mnc, [Mnc1, Mnc2, Mnc3]}, {lac, Lac}, {rnc_id, Rnc}];
167decode_cid_ie(?CELL_ID_UTRAN_RNC, Remain) ->
168 <<Rnc:16/big>> = Remain,
169 [{rnc_id, Rnc}];
170decode_cid_ie(?CELL_ID_UTRAN_LAC_RNC, Remain) ->
171 <<Lac:16/big, Rnc:16/big>> = Remain,
172 [{lac, Lac}, {rnc_id, Rnc}].
173
174decode_cid_list(Discr, Data, List) ->
175 case Discr of
176 ?CELL_ID_WHOLE_GLOBAL -> Len = 7;
177 ?CELL_ID_LAC_AND_CI -> Len = 4;
178 ?CELL_ID_CI -> Len = 2;
179 ?CELL_ID_NO_CELL -> Len = 0;
180 ?CELL_ID_UTRAN_PLMN_LAC_RNC -> Len = 7;
181 ?CELL_ID_UTRAN_RNC -> Len = 2;
182 ?CELL_ID_UTRAN_LAC_RNC -> Len = 4
183 end,
184 <<Subset:Len/binary, Remain/binary>> = Data,
185 Elem = {cell_id, decode_cid_ie(Discr, Subset)},
186 decode_cid_list(Discr, Remain, List ++ [Elem]).
187
188
189
190bin_bcd2str(BcdBin) when is_binary(BcdBin) ->
191 bin_bcd2str(BcdBin, []).
192bin_bcd2str(<<>>, List) ->
193 List;
194bin_bcd2str(BcdBin, List) ->
195 <<Nibble:4, Remain/bitstring>> = BcdBin,
196 Char = "0" + Nibble,
197 bin_bcd2str(Remain, List ++ [Char]).