blob: ab191c84d83f047f86dae6a82e0c536f4c7f5604 [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
Harald Welte2a91a012011-03-11 16:28:14 +0100165% Table 26/Q.763: Confusion
166parse_isup_msgt(M, VarAndOpt) when
167 M == ?ISUP_MSGT_REL;
168 M == ?ISUP_MSGT_CFN ->
169 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100170 % V: Cause indicators
Harald Welte2a91a012011-03-11 16:28:14 +0100171 CauseIndLen = binary:at(VarAndOpt, PtrVar),
172 CauseInd = binary:part(VarAndOpt, PtrVar+1, CauseIndLen),
Harald Welte86494e82011-01-21 12:13:35 +0000173 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
174 case PtrOpt of
175 0 ->
176 Opts = [];
177 _ ->
178 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
179 Opts = parse_isup_opts(Remain)
180 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100181 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100182% Table C-19 Subsequent address
Harald Welte2a91a012011-03-11 16:28:14 +0100183parse_isup_msgt(?ISUP_MSGT_SAM, VarAndOpt) ->
184 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100185 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100186 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
187 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
188 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
189 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100190 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100191 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100192% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100193parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100194 <<SuspResInd:8, Remain/binary>> = Bin,
195 FixedOpts = [{susp_res_ind, SuspResInd}],
Harald Weltef48736b2011-01-21 14:34:32 +0100196 Opts = parse_isup_opts_ptr(Remain),
Harald Welte781d98e2011-03-11 16:48:47 +0100197 FixedOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100198% Table C-23
199parse_isup_msgt(M, <<>>) when
200 M == ?ISUP_MSGT_BLO;
201 M == ?ISUP_MSGT_BLA;
202 M == ?ISUP_MSGT_CCR;
203 M == ?ISUP_MSGT_RSC;
204 M == ?ISUP_MSGT_UBL;
205 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100206 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100207% Table C-25
208parse_isup_msgt(M, Bin) when
209 M == ?ISUP_MSGT_CGB;
210 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100211 M == ?ISUP_MSGT_CGU;
212 M == ?ISUP_MSGT_CGUA ->
213 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100214 FixedOpts = [{cg_supv_msgt, CGMsgt}],
215 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100216 RangStsLen = binary:at(VarBin, PtrVar-1),
217 RangeStatus = binary:part(VarBin, PtrVar, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100218 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
219 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100220% Table C-26 Circuit group reset
221parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte661e3812011-03-10 10:22:04 +0100222 <<PtrVar:8, _VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100223 % V: Range without status
Harald Welte661e3812011-03-10 10:22:04 +0100224 RangeLen = binary:at(Bin, PtrVar),
225 Range = binary:part(Bin, PtrVar+1, RangeLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100226 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100227
228
Harald Welte01f8ea32011-01-17 21:30:42 +0100229parse_isup_msg(DataBin) when is_binary(DataBin) ->
230 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100231 Opts = parse_isup_msgt(MsgType, Remain),
232 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100233
234
Harald Welte01f8ea32011-01-17 21:30:42 +0100235% encode a phone number from a list of digits into the BCD binary sequence
Harald Weltec8d06c42011-02-09 22:27:19 +0100236encode_isup_party(BcdInt) when is_integer(BcdInt) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100237 BcdList = osmo_util:int2digit_list(BcdInt),
Harald Weltec8d06c42011-02-09 22:27:19 +0100238 encode_isup_party(BcdList);
239encode_isup_party(BcdList) when is_list(BcdList) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100240 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100241encode_isup_party([], Bin, NumDigits) ->
242 case NumDigits rem 2 of
243 1 ->
244 {Bin, 1};
245 0 ->
246 {Bin, 0}
247 end;
248encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100249 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
250encode_isup_party([Last], Bin, NumDigits) ->
251 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100252
Harald Weltede30a872011-01-16 17:12:56 +0100253% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100254encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100255 #party_number{nature_of_addr_ind = Nature,
256 internal_net_num = Inn,
257 numbering_plan = NumPlan,
258 phone_number= PhoneNum}) ->
259 % C.3.7 Called Party Number
260 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100261 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100262encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100263 #party_number{nature_of_addr_ind = Nature,
264 number_incompl_ind = Ni,
265 numbering_plan = NumPlan,
266 present_restrict = PresRestr,
267 screening_ind = Screen,
268 phone_number= PhoneNum}) ->
269 % C.3.8 Calling Party Number
270 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
271 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100272encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100273 #party_number{nature_of_addr_ind = Nature,
274 numbering_plan = NumPlan,
275 present_restrict = PresRestr,
276 screening_ind = Screen,
277 phone_number = PhoneNum}) ->
278 % C.3.14 Connected Number
279 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
280 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100281encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
282 #party_number{phone_number = PhoneNum}) ->
283 % C.3.32 Subsequent Number
284 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
285 <<OddEven:1, 0:7, PhoneBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100286encode_isup_par(Atom, _More) when is_atom(Atom) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100287 <<>>;
288encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100289 Binary.
290
Harald Welte84cc60d2011-01-18 18:25:53 +0100291% encode a single OPTIONAL parameter (TLV type), skip all others
Harald Weltef48736b2011-01-21 14:34:32 +0100292encode_isup_optpar(ParNum, _ParBody) when is_atom(ParNum) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100293 <<>>;
294encode_isup_optpar(ParNum, ParBody) ->
295 ParBin = encode_isup_par(ParNum, ParBody),
296 ParLen = byte_size(ParBin),
297 <<ParNum:8, ParLen:8, ParBin/binary>>.
298
Harald Weltef48736b2011-01-21 14:34:32 +0100299% recursive function to encode all optional parameters
Harald Welte84cc60d2011-01-18 18:25:53 +0100300encode_isup_opts([], OutBin) ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100301 % terminate with end-of-options, but only if we have options
302 case OutBin of
303 <<>> ->
304 OutBin;
305 _ ->
306 <<OutBin/binary, 0:8>>
307 end;
Harald Welte84cc60d2011-01-18 18:25:53 +0100308encode_isup_opts([Opt|OptPropList], OutBin) ->
309 {OptType, OptBody} = Opt,
310 OptBin = encode_isup_optpar(OptType, OptBody),
311 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
312encode_isup_opts(OptPropList) ->
313 encode_isup_opts(OptPropList, <<>>).
314
315encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
316 <<Cic:12/little, 0:4, MsgType:8>>.
317
Harald Welteed4c9ea2011-01-21 16:58:19 +0000318% Default case: no fixed and no variable parts, only options
319% ANM, RLC, FOT
320encode_isup_msgt(M, #isup_msg{parameters = Params}) when
321 M == ?ISUP_MSGT_ANM;
322 M == ?ISUP_MSGT_RLC;
323 M == ?ISUP_MSGT_FOT ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100324 OptBin = encode_isup_opts(Params),
325 case OptBin of
326 <<>> -> PtrOpt = 0;
327 _ -> PtrOpt = 1
328 end,
329 <<PtrOpt:8, OptBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100330% Table C-5 Address complete
331encode_isup_msgt(?ISUP_MSGT_ACM, #isup_msg{parameters = Params}) ->
332 BackCallInd = proplists:get_value(backward_call_ind, Params),
333 OptBin = encode_isup_opts(Params),
334 case OptBin of
335 <<>> -> PtrOpt = 0;
336 _ -> PtrOpt = 1
337 end,
338 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
339% Table C-7 Call progress
340encode_isup_msgt(?ISUP_MSGT_CPG, #isup_msg{parameters = Params}) ->
341 EventInf = proplists:get_value(event_info, Params),
342 OptBin = encode_isup_opts(Params),
343 case OptBin of
344 <<>> -> PtrOpt = 0;
345 _ -> PtrOpt = 1
346 end,
347 <<EventInf:8, PtrOpt:8, OptBin/binary>>;
348% Table C-9 Circuit group reset acknowledgement
349encode_isup_msgt(?ISUP_MSGT_GRA, #isup_msg{parameters = Params}) ->
350 % V: Range and status
351 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
352 <<1:8, RangStsLen:8, RangeStatus/binary>>;
353% Table C-11 Connect
354encode_isup_msgt(?ISUP_MSGT_CON, #isup_msg{parameters = Params}) ->
355 BackCallInd = proplists:get_value(backward_call_ind, Params),
356 OptBin = encode_isup_opts(Params),
357 case OptBin of
358 <<>> -> PtrOpt = 0;
359 _ -> PtrOpt = 1
360 end,
361 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
362% Table C-12 Continuity
363encode_isup_msgt(?ISUP_MSGT_COT, #isup_msg{parameters = Params}) ->
364 ContInd = proplists:get_value(continuity_ind, Params),
365 <<ContInd:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100366% Table C-16 Initial address
367encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
368 % Fixed part
369 CINat = proplists:get_value(conn_ind_nature, Params),
370 FwCallInd = proplists:get_value(fw_call_ind, Params),
371 CallingCat = proplists:get_value(calling_cat, Params),
372 TransmReq = proplists:get_value(transm_medium_req, Params),
373 PtrVar = 2, % one byte behind the PtrOpt
374 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
375 % V: Called Party Number
376 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
377 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
378 CalledPartyLen = byte_size(CalledParty),
379 % Optional part
Harald Welted1cb16f2011-01-21 15:48:34 +0000380 Params2 = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
381 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100382 case OptBin of
383 <<>> -> PtrOpt = 0;
384 _ -> PtrOpt = CalledPartyLen + 1 + 1 % 1 byte length, 1 byte start offset
385 end,
386 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>;
387% Table C-17 Release
Harald Welte2a91a012011-03-11 16:28:14 +0100388encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when
389 Msgt == ?ISUP_MSGT_REL;
390 Msgt == ?ISUP_MSGT_CFN ->
Harald Weltef48736b2011-01-21 14:34:32 +0100391 PtrVar = 2, % one byte behind the PtrOpt
392 % V: Cause indicators
393 CauseInd = encode_isup_par(?ISUP_PAR_CAUSE_IND,
394 proplists:get_value(?ISUP_PAR_CAUSE_IND, Params)),
395 CauseIndLen = byte_size(CauseInd),
396 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000397 Params2 = proplists:delete(?ISUP_PAR_CAUSE_IND, Params),
398 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100399 case OptBin of
400 <<>> -> PtrOpt = 0;
401 _ -> PtrOpt = CauseIndLen + 1 + 1 % 1 byte length, 1 byte start offset
402 end,
403 <<PtrVar:8, PtrOpt:8, CauseIndLen:8, CauseInd/binary, OptBin/binary>>;
404% Table C-19 Subsequent address
405encode_isup_msgt(?ISUP_MSGT_SAM, #isup_msg{parameters = Params}) ->
406 PtrVar = 2, % one byte behind the PtrOpt
407 % V: Subsequent number
408 SubseqNum = encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
409 proplists:get_value(?ISUP_PAR_SUBSEQ_NUM, Params)),
410 SubseqNumLen = byte_size(SubseqNum),
411 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000412 Params2 = proplists:delete(?ISUP_PAR_SUBSEQ_NUM, Params),
413 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100414 case OptBin of
415 <<>> -> PtrOpt = 0;
416 _ -> PtrOpt = SubseqNumLen + 1 + 1 % 1 byte length, 1 byte start offset
417 end,
418 <<PtrVar:8, PtrOpt:8, SubseqNumLen:8, SubseqNum/binary, OptBin/binary>>;
419% Table C-21 Suspend, Resume
420encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
421 SuspResInd = proplists:get_value(susp_res_ind, Params),
422 OptBin = encode_isup_opts(Params),
423 case OptBin of
424 <<>> -> PtrOpt = 0;
425 _ -> PtrOpt = 1
426 end,
427 <<SuspResInd:8, PtrOpt:8, OptBin/binary>>;
428% Table C-23
429encode_isup_msgt(M, #isup_msg{}) when
430 M == ?ISUP_MSGT_BLO;
431 M == ?ISUP_MSGT_BLA;
432 M == ?ISUP_MSGT_CCR;
433 M == ?ISUP_MSGT_RSC;
434 M == ?ISUP_MSGT_UBL;
435 M == ?ISUP_MSGT_UBA ->
436 <<>>;
437% Table C-25
438encode_isup_msgt(M, #isup_msg{parameters = Params}) when
439 M == ?ISUP_MSGT_CGB;
440 M == ?ISUP_MSGT_CGBA;
441 M == ?ISUP_MSGT_CGU;
442 M == ?ISUP_MSGT_CGUA ->
443 PtrVar = 1, % one byte behind the PtrVar
444 CGMsgt = proplists:get_value(cg_supv_msgt, Params),
445 % V: Range and status
446 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
447 <<CGMsgt:8, PtrVar:8, RangStsLen:8, RangeStatus/binary>>;
448% Table C-26 Circuit group reset
449encode_isup_msgt(?ISUP_MSGT_GRS, #isup_msg{parameters = Params}) ->
450 PtrVar = 1, % one byte behind the PtrVar
451 {RangeLen, Range} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
452 % V: Range without status
453 <<PtrVar:8, RangeLen:8, Range/binary>>.
Harald Welte84cc60d2011-01-18 18:25:53 +0100454
455encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
456 HdrBin = encode_isup_hdr(Msg),
457 Remain = encode_isup_msgt(MsgType, Msg),
458 <<HdrBin/binary, Remain/binary>>.