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