blob: 175b7cce6b5efe28c1e9c73c5cd9d3fd4b1dfbe1 [file] [log] [blame]
Harald Welte50a44c22011-01-15 21:39:20 +01001% ITU-T Q.76x ISUPcoding / decoding
2
3% (C) 2011 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(isup_codec).
21-author('Harald Welte <laforge@gnumonks.org>').
22-include("isup.hrl").
23
24-export([parse_isup_msg/1, encode_isup_msg/1]).
25
Harald Welte01f8ea32011-01-17 21:30:42 +010026-compile(export_all).
27
Harald Weltede30a872011-01-16 17:12:56 +010028parse_isup_party(<<>>, OddEven, DigitList) ->
29 % in case of odd number of digits, we need to cut the last
30 case OddEven of
31 1 ->
Harald Welte01f8ea32011-01-17 21:30:42 +010032 lists:sublist(DigitList, length(DigitList)-1);
Harald Weltede30a872011-01-16 17:12:56 +010033 0 ->
34 DigitList
35 end;
36parse_isup_party(BcdBin, OddEven, DigitList) ->
37 <<Second:4, First:4, Remain/binary>> = BcdBin,
38 NewDigits = [First, Second],
39 parse_isup_party(Remain, OddEven, DigitList ++ NewDigits).
40
41parse_isup_party(BinBcd, OddEven) when is_binary(BinBcd) ->
42 parse_isup_party(BinBcd, OddEven, []).
43
44
45% parse a single option
Harald Welte01f8ea32011-01-17 21:30:42 +010046parse_isup_opt(OptType = ?ISUP_PAR_CALLED_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010047 % C.3.7 Called Party Number
48 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, Remain/binary>> = Content,
49 PhoneNum = parse_isup_party(Remain, OddEven),
50 {OptType, #party_number{nature_of_addr_ind = Nature,
51 internal_net_num = Inn,
52 numbering_plan = NumPlan,
53 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010054parse_isup_opt(OptType = ?ISUP_PAR_CALLING_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010055 % C.3.8 Calling Party Number
56 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
57 PhoneNum = parse_isup_party(Remain, OddEven),
58 {OptType, #party_number{nature_of_addr_ind = Nature,
59 number_incompl_ind = Ni,
60 numbering_plan = NumPlan,
61 present_restrict = PresRestr,
62 screening_ind = Screen,
63 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010064parse_isup_opt(OptType = ?ISUP_PAR_CONNECTED_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010065 % C.3.14 Connected Number
66 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
67 PhoneNum = parse_isup_party(Remain, OddEven),
68 {OptType, #party_number{nature_of_addr_ind = Nature,
69 numbering_plan = NumPlan,
70 present_restrict = PresRestr,
71 screening_ind = Screen,
72 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010073parse_isup_opt(OptType = ?ISUP_PAR_SUBSEQ_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010074 % C.3.32 Subsequent Number
Harald Welte01f8ea32011-01-17 21:30:42 +010075 <<OddEven:1, 0:7, Remain/binary>> = Content,
Harald Weltede30a872011-01-16 17:12:56 +010076 PhoneNum = parse_isup_party(Remain, OddEven),
77 {OptType, #party_number{phone_number = PhoneNum}};
78parse_isup_opt(OptType, OptLen, Content) ->
79 {OptType, {OptLen, Content}}.
80
81% parse a Binary into a list of options
82parse_isup_opts(<<>>, OptList) ->
83 % empty list
84 OptList;
85parse_isup_opts(<<0>>, OptList) ->
86 % end of options
87 OptList;
88parse_isup_opts(OptBin, OptList) when is_binary(OptBin) ->
89 <<OptType:8, OptLen:8, Content:OptLen/binary, Remain/binary>> = OptBin,
90 NewOpt = parse_isup_opt(OptType, OptLen, Content),
Harald Welte01f8ea32011-01-17 21:30:42 +010091 parse_isup_opts(Remain, OptList ++ [NewOpt]).
92parse_isup_opts(OptBin) ->
93 parse_isup_opts(OptBin, []).
Harald Weltede30a872011-01-16 17:12:56 +010094
Harald Welte50a44c22011-01-15 21:39:20 +010095% References to 'Tabe C-xxx' are to Annex C of Q.767
96
97% Default case: no fixed and no variable parts, only options
98% ANM, RLC, FOT
99parse_isup_msgt(M, Bin) when
100 M == ?ISUP_MSGT_ANM;
101 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +0100102 M == ?ISUP_MSGT_FOT ->
Harald Welte50a44c22011-01-15 21:39:20 +0100103 parse_isup_opts(Bin);
104% Table C-5 Address complete
105parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
106 <<BackCallInd:16, Remain/binary>> = Bin,
107 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltede30a872011-01-16 17:12:56 +0100108 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100109 [BciOpt|Opts];
110% Table C-7 Call progress
111parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
112 <<EventInf:8, Remain/binary>> = Bin,
113 BciOpt = {event_info, EventInf},
Harald Weltede30a872011-01-16 17:12:56 +0100114 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100115 [BciOpt|Opts];
116% Table C-9 Circuit group reset acknowledgement
117parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
118 % V: Range and status
Harald Welte01f8ea32011-01-17 21:30:42 +0100119 <<PtrVar:8, Remain/binary>> = Bin,
120 RangStsLen = binary:at(Remain, PtrVar),
121 RangeStatus = binary:part(Remain, PtrVar+1, RangStsLen),
122 RangeStsTuple = {?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}},
123 [RangeStsTuple];
Harald Welte50a44c22011-01-15 21:39:20 +0100124% Table C-11 Connect
125parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
126 <<BackCallInd:16, Remain/binary>> = Bin,
127 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltede30a872011-01-16 17:12:56 +0100128 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100129 [BciOpt|Opts];
130% Table C-12 Continuity
131parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
132 <<ContInd:8>> = Bin,
133 [{continuity_ind, ContInd}];
134% Table C-16 Initial address
135parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
136 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
137 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
138 {transm_medium_req, TransmReq}],
Harald Welte01f8ea32011-01-17 21:30:42 +0100139 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100140 % V: Called Party Number
Harald Welte01f8ea32011-01-17 21:30:42 +0100141 CalledPartyLen = binary:at(VarAndOpt, PtrVar),
142 CalledParty = binary:part(VarAndOpt, PtrVar+1, CalledPartyLen),
143 VarOpts = [parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, CalledPartyLen, CalledParty)],
144 % Optional part
Harald Welte86494e82011-01-21 12:13:35 +0000145 case PtrOpt of
146 0 ->
147 Opts = [];
148 _ ->
149 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
150 Opts = parse_isup_opts(Remain)
151 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100152 FixedOpts ++ VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100153% Table C-17 Release
154parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100155 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100156 % V: Cause indicators
Harald Welte86494e82011-01-21 12:13:35 +0000157 CauseIndLen = binary:at(VarAndOpt, PtrVar-2),
158 CauseInd = binary:part(VarAndOpt, PtrVar-1, CauseIndLen),
159 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
160 case PtrOpt of
161 0 ->
162 Opts = [];
163 _ ->
164 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
165 Opts = parse_isup_opts(Remain)
166 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100167 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100168% Table C-19 Subsequent address
169parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100170 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100171 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100172 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
173 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
174 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
175 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100176 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100177 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100178% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100179parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100180 <<SuspResInd:8, Remain/binary>> = Bin,
181 FixedOpts = [{susp_res_ind, SuspResInd}],
182 Opts = parse_isup_opts(Remain),
183 [FixedOpts|Opts];
184% Table C-23
185parse_isup_msgt(M, <<>>) when
186 M == ?ISUP_MSGT_BLO;
187 M == ?ISUP_MSGT_BLA;
188 M == ?ISUP_MSGT_CCR;
189 M == ?ISUP_MSGT_RSC;
190 M == ?ISUP_MSGT_UBL;
191 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100192 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100193% Table C-25
194parse_isup_msgt(M, Bin) when
195 M == ?ISUP_MSGT_CGB;
196 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100197 M == ?ISUP_MSGT_CGU;
198 M == ?ISUP_MSGT_CGUA ->
199 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100200 FixedOpts = [{cg_supv_msgt, CGMsgt}],
201 % V: Range and status
Harald Welte01f8ea32011-01-17 21:30:42 +0100202 RangStsLen = binary:at(VarBin, PtrVar),
203 RangeStatus = binary:part(VarBin, PtrVar+1, RangStsLen),
204 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
205 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100206% Table C-26 Circuit group reset
207parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100208 <<PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100209 % V: Range without status
Harald Welte01f8ea32011-01-17 21:30:42 +0100210 RangeLen = binary:at(VarBin, PtrVar),
211 Range = binary:part(VarBin, PtrVar+1, RangeLen),
212 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100213
214
Harald Welte01f8ea32011-01-17 21:30:42 +0100215parse_isup_msg(DataBin) when is_binary(DataBin) ->
216 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100217 Opts = parse_isup_msgt(MsgType, Remain),
218 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100219
220
Harald Welte01f8ea32011-01-17 21:30:42 +0100221% encode a phone number from a list of digits into the BCD binary sequence
Harald Weltede30a872011-01-16 17:12:56 +0100222encode_isup_party(BcdList) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100223 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100224encode_isup_party([], Bin, NumDigits) ->
225 case NumDigits rem 2 of
226 1 ->
227 {Bin, 1};
228 0 ->
229 {Bin, 0}
230 end;
231encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100232 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
233encode_isup_party([Last], Bin, NumDigits) ->
234 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100235
Harald Weltede30a872011-01-16 17:12:56 +0100236% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100237encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100238 #party_number{nature_of_addr_ind = Nature,
239 internal_net_num = Inn,
240 numbering_plan = NumPlan,
241 phone_number= PhoneNum}) ->
242 % C.3.7 Called Party Number
243 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100244 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100245encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100246 #party_number{nature_of_addr_ind = Nature,
247 number_incompl_ind = Ni,
248 numbering_plan = NumPlan,
249 present_restrict = PresRestr,
250 screening_ind = Screen,
251 phone_number= PhoneNum}) ->
252 % C.3.8 Calling Party Number
253 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
254 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100255encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100256 #party_number{nature_of_addr_ind = Nature,
257 numbering_plan = NumPlan,
258 present_restrict = PresRestr,
259 screening_ind = Screen,
260 phone_number = PhoneNum}) ->
261 % C.3.14 Connected Number
262 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
263 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100264encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
265 #party_number{phone_number = PhoneNum}) ->
266 % C.3.32 Subsequent Number
267 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
268 <<OddEven:1, 0:7, PhoneBin/binary>>;
269encode_isup_par(Atom, More) when is_atom(Atom) ->
270 <<>>;
271encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100272 Binary.
273
Harald Welte84cc60d2011-01-18 18:25:53 +0100274% encode a single OPTIONAL parameter (TLV type), skip all others
275encode_isup_optpar(ParNum, ParBody) when is_atom(ParNum) ->
276 <<>>;
277encode_isup_optpar(ParNum, ParBody) ->
278 ParBin = encode_isup_par(ParNum, ParBody),
279 ParLen = byte_size(ParBin),
280 <<ParNum:8, ParLen:8, ParBin/binary>>.
281
282% recursive function to encode all optional parameters
283encode_isup_opts([], OutBin) ->
284 OutBin;
285encode_isup_opts([Opt|OptPropList], OutBin) ->
286 {OptType, OptBody} = Opt,
287 OptBin = encode_isup_optpar(OptType, OptBody),
288 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
289encode_isup_opts(OptPropList) ->
290 encode_isup_opts(OptPropList, <<>>).
291
292encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
293 <<Cic:12/little, 0:4, MsgType:8>>.
294
295% Table C-16 Initial address
296encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
297 % Fixed part
298 CINat = proplists:get_value(conn_ind_nature, Params),
299 FwCallInd = proplists:get_value(fw_call_ind, Params),
300 CallingCat = proplists:get_value(calling_cat, Params),
301 TransmReq = proplists:get_value(transm_medium_req, Params),
302 PtrVar = 2, % one byte behind the PtrOpt
303 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
304 % V: Called Party Number
305 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
306 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
307 CalledPartyLen = byte_size(CalledParty),
308 % Optional part
309 PtrOpt = CalledPartyLen + 1 + 1, % 1 byte length, 1 byte start offset
310 OptBin = encode_isup_opts(Params),
311 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>.
312
313encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
314 HdrBin = encode_isup_hdr(Msg),
315 Remain = encode_isup_msgt(MsgType, Msg),
316 <<HdrBin/binary, Remain/binary>>.