blob: aafa507c41b93ce7116e146d7f04bee368735cdf [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
Harald Welte36158492011-02-09 21:42:34 +010024-export([parse_isup_msg/1, encode_isup_msg/1, parse_isup_party/2, encode_isup_party/1]).
Harald Welte50a44c22011-01-15 21:39:20 +010025
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 Weltec8d06c42011-02-09 22:27:19 +010032 lists:sublist(DigitList, length(DigitList)-1);
Harald Weltede30a872011-01-16 17:12:56 +010033 0 ->
Harald Weltec8d06c42011-02-09 22:27:19 +010034 DigitList
35 end;
Harald Weltede30a872011-01-16 17:12:56 +010036parse_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 Weltef48736b2011-01-21 14:34:32 +010095% Parse options preceeded by 1 byte OptPtr
96parse_isup_opts_ptr(OptBinPtr) ->
97 OptPtr = binary:at(OptBinPtr, 0),
98 case OptPtr of
99 0 ->
100 [];
101 _ ->
102 OptBin = binary:part(OptBinPtr, OptPtr, byte_size(OptBinPtr)-OptPtr),
103 parse_isup_opts(OptBin, [])
104 end.
105
Harald Welte50a44c22011-01-15 21:39:20 +0100106% References to 'Tabe C-xxx' are to Annex C of Q.767
107
108% Default case: no fixed and no variable parts, only options
109% ANM, RLC, FOT
110parse_isup_msgt(M, Bin) when
111 M == ?ISUP_MSGT_ANM;
112 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +0100113 M == ?ISUP_MSGT_FOT ->
Harald Weltef48736b2011-01-21 14:34:32 +0100114 parse_isup_opts_ptr(Bin);
Harald Welte50a44c22011-01-15 21:39:20 +0100115% Table C-5 Address complete
116parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
117 <<BackCallInd:16, Remain/binary>> = Bin,
118 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100119 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100120 [BciOpt|Opts];
121% Table C-7 Call progress
122parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
123 <<EventInf:8, Remain/binary>> = Bin,
124 BciOpt = {event_info, EventInf},
Harald Weltef48736b2011-01-21 14:34:32 +0100125 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100126 [BciOpt|Opts];
127% Table C-9 Circuit group reset acknowledgement
128parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
129 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100130 <<PtrVar:8, _Remain/binary>> = Bin,
131 RangStsLen = binary:at(Bin, PtrVar),
132 RangeStatus = binary:part(Bin, PtrVar+1, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100133 RangeStsTuple = {?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}},
134 [RangeStsTuple];
Harald Welte50a44c22011-01-15 21:39:20 +0100135% Table C-11 Connect
136parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
137 <<BackCallInd:16, Remain/binary>> = Bin,
138 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100139 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100140 [BciOpt|Opts];
141% Table C-12 Continuity
142parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
143 <<ContInd:8>> = Bin,
144 [{continuity_ind, ContInd}];
145% Table C-16 Initial address
146parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
147 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
148 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
149 {transm_medium_req, TransmReq}],
Harald Welte01f8ea32011-01-17 21:30:42 +0100150 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100151 % V: Called Party Number
Harald Welte01f8ea32011-01-17 21:30:42 +0100152 CalledPartyLen = binary:at(VarAndOpt, PtrVar),
153 CalledParty = binary:part(VarAndOpt, PtrVar+1, CalledPartyLen),
154 VarOpts = [parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, CalledPartyLen, CalledParty)],
155 % Optional part
Harald Welte86494e82011-01-21 12:13:35 +0000156 case PtrOpt of
157 0 ->
158 Opts = [];
159 _ ->
160 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
161 Opts = parse_isup_opts(Remain)
162 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100163 FixedOpts ++ VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100164% Table C-17 Release
165parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100166 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100167 % V: Cause indicators
Harald Welte86494e82011-01-21 12:13:35 +0000168 CauseIndLen = binary:at(VarAndOpt, PtrVar-2),
169 CauseInd = binary:part(VarAndOpt, PtrVar-1, CauseIndLen),
170 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
171 case PtrOpt of
172 0 ->
173 Opts = [];
174 _ ->
175 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
176 Opts = parse_isup_opts(Remain)
177 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100178 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100179% Table C-19 Subsequent address
180parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100181 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100182 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100183 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
184 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
185 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
186 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100187 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100188 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100189% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100190parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100191 <<SuspResInd:8, Remain/binary>> = Bin,
192 FixedOpts = [{susp_res_ind, SuspResInd}],
Harald Weltef48736b2011-01-21 14:34:32 +0100193 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100194 [FixedOpts|Opts];
195% Table C-23
196parse_isup_msgt(M, <<>>) when
197 M == ?ISUP_MSGT_BLO;
198 M == ?ISUP_MSGT_BLA;
199 M == ?ISUP_MSGT_CCR;
200 M == ?ISUP_MSGT_RSC;
201 M == ?ISUP_MSGT_UBL;
202 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100203 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100204% Table C-25
205parse_isup_msgt(M, Bin) when
206 M == ?ISUP_MSGT_CGB;
207 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100208 M == ?ISUP_MSGT_CGU;
209 M == ?ISUP_MSGT_CGUA ->
210 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100211 FixedOpts = [{cg_supv_msgt, CGMsgt}],
212 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100213 RangStsLen = binary:at(VarBin, PtrVar-1),
214 RangeStatus = binary:part(VarBin, PtrVar, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100215 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
216 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100217% Table C-26 Circuit group reset
218parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte661e3812011-03-10 10:22:04 +0100219 <<PtrVar:8, _VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100220 % V: Range without status
Harald Welte661e3812011-03-10 10:22:04 +0100221 RangeLen = binary:at(Bin, PtrVar),
222 Range = binary:part(Bin, PtrVar+1, RangeLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100223 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100224
225
Harald Welte01f8ea32011-01-17 21:30:42 +0100226parse_isup_msg(DataBin) when is_binary(DataBin) ->
227 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100228 Opts = parse_isup_msgt(MsgType, Remain),
229 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100230
231
Harald Welte01f8ea32011-01-17 21:30:42 +0100232% encode a phone number from a list of digits into the BCD binary sequence
Harald Weltec8d06c42011-02-09 22:27:19 +0100233encode_isup_party(BcdInt) when is_integer(BcdInt) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100234 BcdList = osmo_util:int2digit_list(BcdInt),
Harald Weltec8d06c42011-02-09 22:27:19 +0100235 encode_isup_party(BcdList);
236encode_isup_party(BcdList) when is_list(BcdList) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100237 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100238encode_isup_party([], Bin, NumDigits) ->
239 case NumDigits rem 2 of
240 1 ->
241 {Bin, 1};
242 0 ->
243 {Bin, 0}
244 end;
245encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100246 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
247encode_isup_party([Last], Bin, NumDigits) ->
248 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100249
Harald Weltede30a872011-01-16 17:12:56 +0100250% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100251encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100252 #party_number{nature_of_addr_ind = Nature,
253 internal_net_num = Inn,
254 numbering_plan = NumPlan,
255 phone_number= PhoneNum}) ->
256 % C.3.7 Called Party Number
257 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100258 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100259encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100260 #party_number{nature_of_addr_ind = Nature,
261 number_incompl_ind = Ni,
262 numbering_plan = NumPlan,
263 present_restrict = PresRestr,
264 screening_ind = Screen,
265 phone_number= PhoneNum}) ->
266 % C.3.8 Calling Party Number
267 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
268 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100269encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100270 #party_number{nature_of_addr_ind = Nature,
271 numbering_plan = NumPlan,
272 present_restrict = PresRestr,
273 screening_ind = Screen,
274 phone_number = PhoneNum}) ->
275 % C.3.14 Connected Number
276 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
277 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100278encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
279 #party_number{phone_number = PhoneNum}) ->
280 % C.3.32 Subsequent Number
281 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
282 <<OddEven:1, 0:7, PhoneBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100283encode_isup_par(Atom, _More) when is_atom(Atom) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100284 <<>>;
285encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100286 Binary.
287
Harald Welte84cc60d2011-01-18 18:25:53 +0100288% encode a single OPTIONAL parameter (TLV type), skip all others
Harald Weltef48736b2011-01-21 14:34:32 +0100289encode_isup_optpar(ParNum, _ParBody) when is_atom(ParNum) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100290 <<>>;
291encode_isup_optpar(ParNum, ParBody) ->
292 ParBin = encode_isup_par(ParNum, ParBody),
293 ParLen = byte_size(ParBin),
294 <<ParNum:8, ParLen:8, ParBin/binary>>.
295
Harald Weltef48736b2011-01-21 14:34:32 +0100296% recursive function to encode all optional parameters
Harald Welte84cc60d2011-01-18 18:25:53 +0100297encode_isup_opts([], OutBin) ->
Harald Welte548f93b2011-01-21 16:06:49 +0000298 <<OutBin/binary, 0:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100299encode_isup_opts([Opt|OptPropList], OutBin) ->
300 {OptType, OptBody} = Opt,
301 OptBin = encode_isup_optpar(OptType, OptBody),
302 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
303encode_isup_opts(OptPropList) ->
304 encode_isup_opts(OptPropList, <<>>).
305
306encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
307 <<Cic:12/little, 0:4, MsgType:8>>.
308
Harald Welteed4c9ea2011-01-21 16:58:19 +0000309% Default case: no fixed and no variable parts, only options
310% ANM, RLC, FOT
311encode_isup_msgt(M, #isup_msg{parameters = Params}) when
312 M == ?ISUP_MSGT_ANM;
313 M == ?ISUP_MSGT_RLC;
314 M == ?ISUP_MSGT_FOT ->
315 encode_isup_opts(Params);
Harald Weltef48736b2011-01-21 14:34:32 +0100316% Table C-5 Address complete
317encode_isup_msgt(?ISUP_MSGT_ACM, #isup_msg{parameters = Params}) ->
318 BackCallInd = proplists:get_value(backward_call_ind, Params),
319 OptBin = encode_isup_opts(Params),
320 case OptBin of
321 <<>> -> PtrOpt = 0;
322 _ -> PtrOpt = 1
323 end,
324 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
325% Table C-7 Call progress
326encode_isup_msgt(?ISUP_MSGT_CPG, #isup_msg{parameters = Params}) ->
327 EventInf = proplists:get_value(event_info, Params),
328 OptBin = encode_isup_opts(Params),
329 case OptBin of
330 <<>> -> PtrOpt = 0;
331 _ -> PtrOpt = 1
332 end,
333 <<EventInf:8, PtrOpt:8, OptBin/binary>>;
334% Table C-9 Circuit group reset acknowledgement
335encode_isup_msgt(?ISUP_MSGT_GRA, #isup_msg{parameters = Params}) ->
336 % V: Range and status
337 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
338 <<1:8, RangStsLen:8, RangeStatus/binary>>;
339% Table C-11 Connect
340encode_isup_msgt(?ISUP_MSGT_CON, #isup_msg{parameters = Params}) ->
341 BackCallInd = proplists:get_value(backward_call_ind, Params),
342 OptBin = encode_isup_opts(Params),
343 case OptBin of
344 <<>> -> PtrOpt = 0;
345 _ -> PtrOpt = 1
346 end,
347 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
348% Table C-12 Continuity
349encode_isup_msgt(?ISUP_MSGT_COT, #isup_msg{parameters = Params}) ->
350 ContInd = proplists:get_value(continuity_ind, Params),
351 <<ContInd:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100352% Table C-16 Initial address
353encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
354 % Fixed part
355 CINat = proplists:get_value(conn_ind_nature, Params),
356 FwCallInd = proplists:get_value(fw_call_ind, Params),
357 CallingCat = proplists:get_value(calling_cat, Params),
358 TransmReq = proplists:get_value(transm_medium_req, Params),
359 PtrVar = 2, % one byte behind the PtrOpt
360 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
361 % V: Called Party Number
362 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
363 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
364 CalledPartyLen = byte_size(CalledParty),
365 % Optional part
Harald Welted1cb16f2011-01-21 15:48:34 +0000366 Params2 = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
367 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100368 case OptBin of
369 <<>> -> PtrOpt = 0;
370 _ -> PtrOpt = CalledPartyLen + 1 + 1 % 1 byte length, 1 byte start offset
371 end,
372 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>;
373% Table C-17 Release
374encode_isup_msgt(?ISUP_MSGT_REL, #isup_msg{parameters = Params}) ->
375 PtrVar = 2, % one byte behind the PtrOpt
376 % V: Cause indicators
377 CauseInd = encode_isup_par(?ISUP_PAR_CAUSE_IND,
378 proplists:get_value(?ISUP_PAR_CAUSE_IND, Params)),
379 CauseIndLen = byte_size(CauseInd),
380 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000381 Params2 = proplists:delete(?ISUP_PAR_CAUSE_IND, Params),
382 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100383 case OptBin of
384 <<>> -> PtrOpt = 0;
385 _ -> PtrOpt = CauseIndLen + 1 + 1 % 1 byte length, 1 byte start offset
386 end,
387 <<PtrVar:8, PtrOpt:8, CauseIndLen:8, CauseInd/binary, OptBin/binary>>;
388% Table C-19 Subsequent address
389encode_isup_msgt(?ISUP_MSGT_SAM, #isup_msg{parameters = Params}) ->
390 PtrVar = 2, % one byte behind the PtrOpt
391 % V: Subsequent number
392 SubseqNum = encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
393 proplists:get_value(?ISUP_PAR_SUBSEQ_NUM, Params)),
394 SubseqNumLen = byte_size(SubseqNum),
395 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000396 Params2 = proplists:delete(?ISUP_PAR_SUBSEQ_NUM, Params),
397 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100398 case OptBin of
399 <<>> -> PtrOpt = 0;
400 _ -> PtrOpt = SubseqNumLen + 1 + 1 % 1 byte length, 1 byte start offset
401 end,
402 <<PtrVar:8, PtrOpt:8, SubseqNumLen:8, SubseqNum/binary, OptBin/binary>>;
403% Table C-21 Suspend, Resume
404encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
405 SuspResInd = proplists:get_value(susp_res_ind, Params),
406 OptBin = encode_isup_opts(Params),
407 case OptBin of
408 <<>> -> PtrOpt = 0;
409 _ -> PtrOpt = 1
410 end,
411 <<SuspResInd:8, PtrOpt:8, OptBin/binary>>;
412% Table C-23
413encode_isup_msgt(M, #isup_msg{}) when
414 M == ?ISUP_MSGT_BLO;
415 M == ?ISUP_MSGT_BLA;
416 M == ?ISUP_MSGT_CCR;
417 M == ?ISUP_MSGT_RSC;
418 M == ?ISUP_MSGT_UBL;
419 M == ?ISUP_MSGT_UBA ->
420 <<>>;
421% Table C-25
422encode_isup_msgt(M, #isup_msg{parameters = Params}) when
423 M == ?ISUP_MSGT_CGB;
424 M == ?ISUP_MSGT_CGBA;
425 M == ?ISUP_MSGT_CGU;
426 M == ?ISUP_MSGT_CGUA ->
427 PtrVar = 1, % one byte behind the PtrVar
428 CGMsgt = proplists:get_value(cg_supv_msgt, Params),
429 % V: Range and status
430 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
431 <<CGMsgt:8, PtrVar:8, RangStsLen:8, RangeStatus/binary>>;
432% Table C-26 Circuit group reset
433encode_isup_msgt(?ISUP_MSGT_GRS, #isup_msg{parameters = Params}) ->
434 PtrVar = 1, % one byte behind the PtrVar
435 {RangeLen, Range} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
436 % V: Range without status
437 <<PtrVar:8, RangeLen:8, Range/binary>>.
Harald Welte84cc60d2011-01-18 18:25:53 +0100438
439encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
440 HdrBin = encode_isup_hdr(Msg),
441 Remain = encode_isup_msgt(MsgType, Msg),
442 <<HdrBin/binary, Remain/binary>>.