blob: 9df454f2f9638686a2bbdebd74fcd7d4394a9f86 [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 Welteba6fdbb2011-01-23 22:04:39 +010024-export([parse_isup_msg/1, encode_isup_msg/1, parse_isup_party/2]).
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 Welte93b2ab52011-02-06 21:48:58 +010032 L = lists:sublist(DigitList, length(DigitList)-1);
Harald Weltede30a872011-01-16 17:12:56 +010033 0 ->
Harald Welte93b2ab52011-02-06 21:48:58 +010034 L = DigitList
35 end,
36 osmo_util:digit_list2int(L);
Harald Weltede30a872011-01-16 17:12:56 +010037parse_isup_party(BcdBin, OddEven, DigitList) ->
38 <<Second:4, First:4, Remain/binary>> = BcdBin,
39 NewDigits = [First, Second],
40 parse_isup_party(Remain, OddEven, DigitList ++ NewDigits).
41
42parse_isup_party(BinBcd, OddEven) when is_binary(BinBcd) ->
43 parse_isup_party(BinBcd, OddEven, []).
44
45
46% parse a single option
Harald Welte01f8ea32011-01-17 21:30:42 +010047parse_isup_opt(OptType = ?ISUP_PAR_CALLED_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010048 % C.3.7 Called Party Number
49 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, Remain/binary>> = Content,
50 PhoneNum = parse_isup_party(Remain, OddEven),
51 {OptType, #party_number{nature_of_addr_ind = Nature,
52 internal_net_num = Inn,
53 numbering_plan = NumPlan,
54 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010055parse_isup_opt(OptType = ?ISUP_PAR_CALLING_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010056 % C.3.8 Calling Party Number
57 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
58 PhoneNum = parse_isup_party(Remain, OddEven),
59 {OptType, #party_number{nature_of_addr_ind = Nature,
60 number_incompl_ind = Ni,
61 numbering_plan = NumPlan,
62 present_restrict = PresRestr,
63 screening_ind = Screen,
64 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010065parse_isup_opt(OptType = ?ISUP_PAR_CONNECTED_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010066 % C.3.14 Connected Number
67 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
68 PhoneNum = parse_isup_party(Remain, OddEven),
69 {OptType, #party_number{nature_of_addr_ind = Nature,
70 numbering_plan = NumPlan,
71 present_restrict = PresRestr,
72 screening_ind = Screen,
73 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010074parse_isup_opt(OptType = ?ISUP_PAR_SUBSEQ_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010075 % C.3.32 Subsequent Number
Harald Welte01f8ea32011-01-17 21:30:42 +010076 <<OddEven:1, 0:7, Remain/binary>> = Content,
Harald Weltede30a872011-01-16 17:12:56 +010077 PhoneNum = parse_isup_party(Remain, OddEven),
78 {OptType, #party_number{phone_number = PhoneNum}};
79parse_isup_opt(OptType, OptLen, Content) ->
80 {OptType, {OptLen, Content}}.
81
82% parse a Binary into a list of options
83parse_isup_opts(<<>>, OptList) ->
84 % empty list
85 OptList;
86parse_isup_opts(<<0>>, OptList) ->
87 % end of options
88 OptList;
89parse_isup_opts(OptBin, OptList) when is_binary(OptBin) ->
90 <<OptType:8, OptLen:8, Content:OptLen/binary, Remain/binary>> = OptBin,
91 NewOpt = parse_isup_opt(OptType, OptLen, Content),
Harald Welte01f8ea32011-01-17 21:30:42 +010092 parse_isup_opts(Remain, OptList ++ [NewOpt]).
93parse_isup_opts(OptBin) ->
94 parse_isup_opts(OptBin, []).
Harald Weltede30a872011-01-16 17:12:56 +010095
Harald Weltef48736b2011-01-21 14:34:32 +010096% Parse options preceeded by 1 byte OptPtr
97parse_isup_opts_ptr(OptBinPtr) ->
98 OptPtr = binary:at(OptBinPtr, 0),
99 case OptPtr of
100 0 ->
101 [];
102 _ ->
103 OptBin = binary:part(OptBinPtr, OptPtr, byte_size(OptBinPtr)-OptPtr),
104 parse_isup_opts(OptBin, [])
105 end.
106
Harald Welte50a44c22011-01-15 21:39:20 +0100107% References to 'Tabe C-xxx' are to Annex C of Q.767
108
109% Default case: no fixed and no variable parts, only options
110% ANM, RLC, FOT
111parse_isup_msgt(M, Bin) when
112 M == ?ISUP_MSGT_ANM;
113 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +0100114 M == ?ISUP_MSGT_FOT ->
Harald Weltef48736b2011-01-21 14:34:32 +0100115 parse_isup_opts_ptr(Bin);
Harald Welte50a44c22011-01-15 21:39:20 +0100116% Table C-5 Address complete
117parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
118 <<BackCallInd:16, Remain/binary>> = Bin,
119 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100120 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100121 [BciOpt|Opts];
122% Table C-7 Call progress
123parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
124 <<EventInf:8, Remain/binary>> = Bin,
125 BciOpt = {event_info, EventInf},
Harald Weltef48736b2011-01-21 14:34:32 +0100126 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100127 [BciOpt|Opts];
128% Table C-9 Circuit group reset acknowledgement
129parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
130 % V: Range and status
Harald Welte01f8ea32011-01-17 21:30:42 +0100131 <<PtrVar:8, Remain/binary>> = Bin,
132 RangStsLen = binary:at(Remain, PtrVar),
133 RangeStatus = binary:part(Remain, PtrVar+1, RangStsLen),
134 RangeStsTuple = {?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}},
135 [RangeStsTuple];
Harald Welte50a44c22011-01-15 21:39:20 +0100136% Table C-11 Connect
137parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
138 <<BackCallInd:16, Remain/binary>> = Bin,
139 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100140 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100141 [BciOpt|Opts];
142% Table C-12 Continuity
143parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
144 <<ContInd:8>> = Bin,
145 [{continuity_ind, ContInd}];
146% Table C-16 Initial address
147parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
148 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
149 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
150 {transm_medium_req, TransmReq}],
Harald Welte01f8ea32011-01-17 21:30:42 +0100151 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100152 % V: Called Party Number
Harald Welte01f8ea32011-01-17 21:30:42 +0100153 CalledPartyLen = binary:at(VarAndOpt, PtrVar),
154 CalledParty = binary:part(VarAndOpt, PtrVar+1, CalledPartyLen),
155 VarOpts = [parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, CalledPartyLen, CalledParty)],
156 % Optional part
Harald Welte86494e82011-01-21 12:13:35 +0000157 case PtrOpt of
158 0 ->
159 Opts = [];
160 _ ->
161 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
162 Opts = parse_isup_opts(Remain)
163 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100164 FixedOpts ++ VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100165% Table C-17 Release
166parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100167 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100168 % V: Cause indicators
Harald Welte86494e82011-01-21 12:13:35 +0000169 CauseIndLen = binary:at(VarAndOpt, PtrVar-2),
170 CauseInd = binary:part(VarAndOpt, PtrVar-1, CauseIndLen),
171 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
172 case PtrOpt of
173 0 ->
174 Opts = [];
175 _ ->
176 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
177 Opts = parse_isup_opts(Remain)
178 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100179 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100180% Table C-19 Subsequent address
181parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100182 <<PtrVar:8, PtrOpt:8, VarAndOpt/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100183 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100184 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
185 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
186 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
187 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100188 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100189 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100190% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100191parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100192 <<SuspResInd:8, Remain/binary>> = Bin,
193 FixedOpts = [{susp_res_ind, SuspResInd}],
Harald Weltef48736b2011-01-21 14:34:32 +0100194 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100195 [FixedOpts|Opts];
196% Table C-23
197parse_isup_msgt(M, <<>>) when
198 M == ?ISUP_MSGT_BLO;
199 M == ?ISUP_MSGT_BLA;
200 M == ?ISUP_MSGT_CCR;
201 M == ?ISUP_MSGT_RSC;
202 M == ?ISUP_MSGT_UBL;
203 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100204 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100205% Table C-25
206parse_isup_msgt(M, Bin) when
207 M == ?ISUP_MSGT_CGB;
208 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100209 M == ?ISUP_MSGT_CGU;
210 M == ?ISUP_MSGT_CGUA ->
211 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100212 FixedOpts = [{cg_supv_msgt, CGMsgt}],
213 % V: Range and status
Harald Welte01f8ea32011-01-17 21:30:42 +0100214 RangStsLen = binary:at(VarBin, PtrVar),
215 RangeStatus = binary:part(VarBin, PtrVar+1, RangStsLen),
216 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
217 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100218% Table C-26 Circuit group reset
219parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100220 <<PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100221 % V: Range without status
Harald Welte01f8ea32011-01-17 21:30:42 +0100222 RangeLen = binary:at(VarBin, PtrVar),
223 Range = binary:part(VarBin, PtrVar+1, RangeLen),
224 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100225
226
Harald Welte01f8ea32011-01-17 21:30:42 +0100227parse_isup_msg(DataBin) when is_binary(DataBin) ->
228 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100229 Opts = parse_isup_msgt(MsgType, Remain),
230 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100231
232
Harald Welte01f8ea32011-01-17 21:30:42 +0100233% encode a phone number from a list of digits into the BCD binary sequence
Harald Welte93b2ab52011-02-06 21:48:58 +0100234encode_isup_party(BcdInt) ->
235 BcdList = osmo_util:int2digit_list(BcdInt),
Harald Welte01f8ea32011-01-17 21:30:42 +0100236 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100237encode_isup_party([], Bin, NumDigits) ->
238 case NumDigits rem 2 of
239 1 ->
240 {Bin, 1};
241 0 ->
242 {Bin, 0}
243 end;
244encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100245 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
246encode_isup_party([Last], Bin, NumDigits) ->
247 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100248
Harald Weltede30a872011-01-16 17:12:56 +0100249% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100250encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100251 #party_number{nature_of_addr_ind = Nature,
252 internal_net_num = Inn,
253 numbering_plan = NumPlan,
254 phone_number= PhoneNum}) ->
255 % C.3.7 Called Party Number
256 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100257 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100258encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100259 #party_number{nature_of_addr_ind = Nature,
260 number_incompl_ind = Ni,
261 numbering_plan = NumPlan,
262 present_restrict = PresRestr,
263 screening_ind = Screen,
264 phone_number= PhoneNum}) ->
265 % C.3.8 Calling Party Number
266 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
267 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100268encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100269 #party_number{nature_of_addr_ind = Nature,
270 numbering_plan = NumPlan,
271 present_restrict = PresRestr,
272 screening_ind = Screen,
273 phone_number = PhoneNum}) ->
274 % C.3.14 Connected Number
275 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
276 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100277encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
278 #party_number{phone_number = PhoneNum}) ->
279 % C.3.32 Subsequent Number
280 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
281 <<OddEven:1, 0:7, PhoneBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100282encode_isup_par(Atom, _More) when is_atom(Atom) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100283 <<>>;
284encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100285 Binary.
286
Harald Welte84cc60d2011-01-18 18:25:53 +0100287% encode a single OPTIONAL parameter (TLV type), skip all others
Harald Weltef48736b2011-01-21 14:34:32 +0100288encode_isup_optpar(ParNum, _ParBody) when is_atom(ParNum) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100289 <<>>;
290encode_isup_optpar(ParNum, ParBody) ->
291 ParBin = encode_isup_par(ParNum, ParBody),
292 ParLen = byte_size(ParBin),
293 <<ParNum:8, ParLen:8, ParBin/binary>>.
294
Harald Weltef48736b2011-01-21 14:34:32 +0100295% recursive function to encode all optional parameters
Harald Welte84cc60d2011-01-18 18:25:53 +0100296encode_isup_opts([], OutBin) ->
Harald Welte548f93b2011-01-21 16:06:49 +0000297 <<OutBin/binary, 0:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100298encode_isup_opts([Opt|OptPropList], OutBin) ->
299 {OptType, OptBody} = Opt,
300 OptBin = encode_isup_optpar(OptType, OptBody),
301 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
302encode_isup_opts(OptPropList) ->
303 encode_isup_opts(OptPropList, <<>>).
304
305encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
306 <<Cic:12/little, 0:4, MsgType:8>>.
307
Harald Welteed4c9ea2011-01-21 16:58:19 +0000308% Default case: no fixed and no variable parts, only options
309% ANM, RLC, FOT
310encode_isup_msgt(M, #isup_msg{parameters = Params}) when
311 M == ?ISUP_MSGT_ANM;
312 M == ?ISUP_MSGT_RLC;
313 M == ?ISUP_MSGT_FOT ->
314 encode_isup_opts(Params);
Harald Weltef48736b2011-01-21 14:34:32 +0100315% Table C-5 Address complete
316encode_isup_msgt(?ISUP_MSGT_ACM, #isup_msg{parameters = Params}) ->
317 BackCallInd = proplists:get_value(backward_call_ind, Params),
318 OptBin = encode_isup_opts(Params),
319 case OptBin of
320 <<>> -> PtrOpt = 0;
321 _ -> PtrOpt = 1
322 end,
323 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
324% Table C-7 Call progress
325encode_isup_msgt(?ISUP_MSGT_CPG, #isup_msg{parameters = Params}) ->
326 EventInf = proplists:get_value(event_info, Params),
327 OptBin = encode_isup_opts(Params),
328 case OptBin of
329 <<>> -> PtrOpt = 0;
330 _ -> PtrOpt = 1
331 end,
332 <<EventInf:8, PtrOpt:8, OptBin/binary>>;
333% Table C-9 Circuit group reset acknowledgement
334encode_isup_msgt(?ISUP_MSGT_GRA, #isup_msg{parameters = Params}) ->
335 % V: Range and status
336 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
337 <<1:8, RangStsLen:8, RangeStatus/binary>>;
338% Table C-11 Connect
339encode_isup_msgt(?ISUP_MSGT_CON, #isup_msg{parameters = Params}) ->
340 BackCallInd = proplists:get_value(backward_call_ind, Params),
341 OptBin = encode_isup_opts(Params),
342 case OptBin of
343 <<>> -> PtrOpt = 0;
344 _ -> PtrOpt = 1
345 end,
346 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
347% Table C-12 Continuity
348encode_isup_msgt(?ISUP_MSGT_COT, #isup_msg{parameters = Params}) ->
349 ContInd = proplists:get_value(continuity_ind, Params),
350 <<ContInd:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100351% Table C-16 Initial address
352encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
353 % Fixed part
354 CINat = proplists:get_value(conn_ind_nature, Params),
355 FwCallInd = proplists:get_value(fw_call_ind, Params),
356 CallingCat = proplists:get_value(calling_cat, Params),
357 TransmReq = proplists:get_value(transm_medium_req, Params),
358 PtrVar = 2, % one byte behind the PtrOpt
359 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
360 % V: Called Party Number
361 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
362 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
363 CalledPartyLen = byte_size(CalledParty),
364 % Optional part
Harald Welted1cb16f2011-01-21 15:48:34 +0000365 Params2 = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
366 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100367 case OptBin of
368 <<>> -> PtrOpt = 0;
369 _ -> PtrOpt = CalledPartyLen + 1 + 1 % 1 byte length, 1 byte start offset
370 end,
371 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>;
372% Table C-17 Release
373encode_isup_msgt(?ISUP_MSGT_REL, #isup_msg{parameters = Params}) ->
374 PtrVar = 2, % one byte behind the PtrOpt
375 % V: Cause indicators
376 CauseInd = encode_isup_par(?ISUP_PAR_CAUSE_IND,
377 proplists:get_value(?ISUP_PAR_CAUSE_IND, Params)),
378 CauseIndLen = byte_size(CauseInd),
379 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000380 Params2 = proplists:delete(?ISUP_PAR_CAUSE_IND, Params),
381 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100382 case OptBin of
383 <<>> -> PtrOpt = 0;
384 _ -> PtrOpt = CauseIndLen + 1 + 1 % 1 byte length, 1 byte start offset
385 end,
386 <<PtrVar:8, PtrOpt:8, CauseIndLen:8, CauseInd/binary, OptBin/binary>>;
387% Table C-19 Subsequent address
388encode_isup_msgt(?ISUP_MSGT_SAM, #isup_msg{parameters = Params}) ->
389 PtrVar = 2, % one byte behind the PtrOpt
390 % V: Subsequent number
391 SubseqNum = encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
392 proplists:get_value(?ISUP_PAR_SUBSEQ_NUM, Params)),
393 SubseqNumLen = byte_size(SubseqNum),
394 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000395 Params2 = proplists:delete(?ISUP_PAR_SUBSEQ_NUM, Params),
396 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100397 case OptBin of
398 <<>> -> PtrOpt = 0;
399 _ -> PtrOpt = SubseqNumLen + 1 + 1 % 1 byte length, 1 byte start offset
400 end,
401 <<PtrVar:8, PtrOpt:8, SubseqNumLen:8, SubseqNum/binary, OptBin/binary>>;
402% Table C-21 Suspend, Resume
403encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
404 SuspResInd = proplists:get_value(susp_res_ind, Params),
405 OptBin = encode_isup_opts(Params),
406 case OptBin of
407 <<>> -> PtrOpt = 0;
408 _ -> PtrOpt = 1
409 end,
410 <<SuspResInd:8, PtrOpt:8, OptBin/binary>>;
411% Table C-23
412encode_isup_msgt(M, #isup_msg{}) when
413 M == ?ISUP_MSGT_BLO;
414 M == ?ISUP_MSGT_BLA;
415 M == ?ISUP_MSGT_CCR;
416 M == ?ISUP_MSGT_RSC;
417 M == ?ISUP_MSGT_UBL;
418 M == ?ISUP_MSGT_UBA ->
419 <<>>;
420% Table C-25
421encode_isup_msgt(M, #isup_msg{parameters = Params}) when
422 M == ?ISUP_MSGT_CGB;
423 M == ?ISUP_MSGT_CGBA;
424 M == ?ISUP_MSGT_CGU;
425 M == ?ISUP_MSGT_CGUA ->
426 PtrVar = 1, % one byte behind the PtrVar
427 CGMsgt = proplists:get_value(cg_supv_msgt, Params),
428 % V: Range and status
429 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
430 <<CGMsgt:8, PtrVar:8, RangStsLen:8, RangeStatus/binary>>;
431% Table C-26 Circuit group reset
432encode_isup_msgt(?ISUP_MSGT_GRS, #isup_msg{parameters = Params}) ->
433 PtrVar = 1, % one byte behind the PtrVar
434 {RangeLen, Range} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
435 % V: Range without status
436 <<PtrVar:8, RangeLen:8, Range/binary>>.
Harald Welte84cc60d2011-01-18 18:25:53 +0100437
438encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
439 HdrBin = encode_isup_hdr(Msg),
440 Remain = encode_isup_msgt(MsgType, Msg),
441 <<HdrBin/binary, Remain/binary>>.