blob: dd2149f3c2f2d24d0b123650a970dff34d4b24f9 [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/>.
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 Welte50a44c22011-01-15 21:39:20 +010033
34-module(isup_codec).
35-author('Harald Welte <laforge@gnumonks.org>').
36-include("isup.hrl").
37
Harald Welte049ee732013-06-24 07:59:52 +020038-export([parse_isup_msg/1, encode_isup_msg/1, parse_isup_party/2,
39 encode_isup_party/1, gen_party_number/3]).
Harald Welte50a44c22011-01-15 21:39:20 +010040
Harald Welte01f8ea32011-01-17 21:30:42 +010041-compile(export_all).
42
Harald Welte52725272011-04-02 16:48:50 +020043-compile({parse_transform, exprecs}).
44-export_records([party_number, isup_msg]).
45
Harald Weltede30a872011-01-16 17:12:56 +010046parse_isup_party(<<>>, OddEven, DigitList) ->
47 % in case of odd number of digits, we need to cut the last
48 case OddEven of
49 1 ->
Harald Weltec8d06c42011-02-09 22:27:19 +010050 lists:sublist(DigitList, length(DigitList)-1);
Harald Weltede30a872011-01-16 17:12:56 +010051 0 ->
Harald Weltec8d06c42011-02-09 22:27:19 +010052 DigitList
53 end;
Harald Weltede30a872011-01-16 17:12:56 +010054parse_isup_party(BcdBin, OddEven, DigitList) ->
55 <<Second:4, First:4, Remain/binary>> = BcdBin,
56 NewDigits = [First, Second],
57 parse_isup_party(Remain, OddEven, DigitList ++ NewDigits).
58
59parse_isup_party(BinBcd, OddEven) when is_binary(BinBcd) ->
60 parse_isup_party(BinBcd, OddEven, []).
61
62
63% parse a single option
Harald Welte01f8ea32011-01-17 21:30:42 +010064parse_isup_opt(OptType = ?ISUP_PAR_CALLED_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010065 % C.3.7 Called Party Number
66 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, Remain/binary>> = Content,
67 PhoneNum = parse_isup_party(Remain, OddEven),
68 {OptType, #party_number{nature_of_addr_ind = Nature,
69 internal_net_num = Inn,
70 numbering_plan = NumPlan,
71 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010072parse_isup_opt(OptType = ?ISUP_PAR_CALLING_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010073 % C.3.8 Calling Party Number
74 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
75 PhoneNum = parse_isup_party(Remain, OddEven),
76 {OptType, #party_number{nature_of_addr_ind = Nature,
77 number_incompl_ind = Ni,
78 numbering_plan = NumPlan,
79 present_restrict = PresRestr,
80 screening_ind = Screen,
81 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010082parse_isup_opt(OptType = ?ISUP_PAR_CONNECTED_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010083 % C.3.14 Connected Number
84 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
85 PhoneNum = parse_isup_party(Remain, OddEven),
86 {OptType, #party_number{nature_of_addr_ind = Nature,
87 numbering_plan = NumPlan,
88 present_restrict = PresRestr,
89 screening_ind = Screen,
90 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010091parse_isup_opt(OptType = ?ISUP_PAR_SUBSEQ_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010092 % C.3.32 Subsequent Number
Harald Welte01f8ea32011-01-17 21:30:42 +010093 <<OddEven:1, 0:7, Remain/binary>> = Content,
Harald Weltede30a872011-01-16 17:12:56 +010094 PhoneNum = parse_isup_party(Remain, OddEven),
95 {OptType, #party_number{phone_number = PhoneNum}};
96parse_isup_opt(OptType, OptLen, Content) ->
97 {OptType, {OptLen, Content}}.
98
99% parse a Binary into a list of options
100parse_isup_opts(<<>>, OptList) ->
101 % empty list
102 OptList;
103parse_isup_opts(<<0>>, OptList) ->
104 % end of options
105 OptList;
106parse_isup_opts(OptBin, OptList) when is_binary(OptBin) ->
107 <<OptType:8, OptLen:8, Content:OptLen/binary, Remain/binary>> = OptBin,
108 NewOpt = parse_isup_opt(OptType, OptLen, Content),
Harald Welte01f8ea32011-01-17 21:30:42 +0100109 parse_isup_opts(Remain, OptList ++ [NewOpt]).
110parse_isup_opts(OptBin) ->
111 parse_isup_opts(OptBin, []).
Harald Weltede30a872011-01-16 17:12:56 +0100112
Harald Weltef48736b2011-01-21 14:34:32 +0100113% Parse options preceeded by 1 byte OptPtr
114parse_isup_opts_ptr(OptBinPtr) ->
115 OptPtr = binary:at(OptBinPtr, 0),
116 case OptPtr of
117 0 ->
118 [];
119 _ ->
120 OptBin = binary:part(OptBinPtr, OptPtr, byte_size(OptBinPtr)-OptPtr),
121 parse_isup_opts(OptBin, [])
122 end.
123
Harald Welte50a44c22011-01-15 21:39:20 +0100124% References to 'Tabe C-xxx' are to Annex C of Q.767
125
126% Default case: no fixed and no variable parts, only options
127% ANM, RLC, FOT
128parse_isup_msgt(M, Bin) when
129 M == ?ISUP_MSGT_ANM;
130 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +0100131 M == ?ISUP_MSGT_FOT ->
Harald Weltef48736b2011-01-21 14:34:32 +0100132 parse_isup_opts_ptr(Bin);
Harald Welte50a44c22011-01-15 21:39:20 +0100133% Table C-5 Address complete
134parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
135 <<BackCallInd:16, Remain/binary>> = Bin,
136 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100137 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100138 [BciOpt|Opts];
139% Table C-7 Call progress
140parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
141 <<EventInf:8, Remain/binary>> = Bin,
142 BciOpt = {event_info, EventInf},
Harald Weltef48736b2011-01-21 14:34:32 +0100143 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100144 [BciOpt|Opts];
145% Table C-9 Circuit group reset acknowledgement
146parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
147 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100148 <<PtrVar:8, _Remain/binary>> = Bin,
149 RangStsLen = binary:at(Bin, PtrVar),
150 RangeStatus = binary:part(Bin, PtrVar+1, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100151 RangeStsTuple = {?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}},
152 [RangeStsTuple];
Harald Welte50a44c22011-01-15 21:39:20 +0100153% Table C-11 Connect
154parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
155 <<BackCallInd:16, Remain/binary>> = Bin,
156 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100157 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100158 [BciOpt|Opts];
159% Table C-12 Continuity
160parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
161 <<ContInd:8>> = Bin,
162 [{continuity_ind, ContInd}];
163% Table C-16 Initial address
164parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
165 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
166 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
167 {transm_medium_req, TransmReq}],
Harald Welte01f8ea32011-01-17 21:30:42 +0100168 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100169 % V: Called Party Number
Harald Welte01f8ea32011-01-17 21:30:42 +0100170 CalledPartyLen = binary:at(VarAndOpt, PtrVar),
171 CalledParty = binary:part(VarAndOpt, PtrVar+1, CalledPartyLen),
172 VarOpts = [parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, CalledPartyLen, CalledParty)],
173 % Optional part
Harald Welte86494e82011-01-21 12:13:35 +0000174 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 FixedOpts ++ VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100182% Table C-17 Release
Harald Welte2a91a012011-03-11 16:28:14 +0100183% Table 26/Q.763: Confusion
184parse_isup_msgt(M, VarAndOpt) when
185 M == ?ISUP_MSGT_REL;
186 M == ?ISUP_MSGT_CFN ->
187 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100188 % V: Cause indicators
Harald Welte2a91a012011-03-11 16:28:14 +0100189 CauseIndLen = binary:at(VarAndOpt, PtrVar),
190 CauseInd = binary:part(VarAndOpt, PtrVar+1, CauseIndLen),
Harald Welte86494e82011-01-21 12:13:35 +0000191 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
192 case PtrOpt of
193 0 ->
194 Opts = [];
195 _ ->
196 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
197 Opts = parse_isup_opts(Remain)
198 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100199 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100200% Table C-19 Subsequent address
Harald Welte2a91a012011-03-11 16:28:14 +0100201parse_isup_msgt(?ISUP_MSGT_SAM, VarAndOpt) ->
202 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100203 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100204 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
205 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
206 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
207 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100208 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100209 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100210% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100211parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100212 <<SuspResInd:8, Remain/binary>> = Bin,
213 FixedOpts = [{susp_res_ind, SuspResInd}],
Harald Weltef48736b2011-01-21 14:34:32 +0100214 Opts = parse_isup_opts_ptr(Remain),
Harald Welte781d98e2011-03-11 16:48:47 +0100215 FixedOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100216% Table C-23
217parse_isup_msgt(M, <<>>) when
218 M == ?ISUP_MSGT_BLO;
219 M == ?ISUP_MSGT_BLA;
220 M == ?ISUP_MSGT_CCR;
221 M == ?ISUP_MSGT_RSC;
222 M == ?ISUP_MSGT_UBL;
223 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100224 [];
Harald Welte2695c3b2011-04-14 11:42:30 +0200225% Table 39/Q.763 messages for national use, fixed length 1 byte msgtype
226parse_isup_msgt(M, <<>>) when
227 M == ?ISUP_MSGT_LPA;
228 M == ?ISUP_MSGT_OLM;
229 M == ?ISUP_MSGT_UCIC ->
230 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100231% Table C-25
232parse_isup_msgt(M, Bin) when
233 M == ?ISUP_MSGT_CGB;
234 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100235 M == ?ISUP_MSGT_CGU;
236 M == ?ISUP_MSGT_CGUA ->
237 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100238 FixedOpts = [{cg_supv_msgt, CGMsgt}],
239 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100240 RangStsLen = binary:at(VarBin, PtrVar-1),
241 RangeStatus = binary:part(VarBin, PtrVar, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100242 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
243 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100244% Table C-26 Circuit group reset
245parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte661e3812011-03-10 10:22:04 +0100246 <<PtrVar:8, _VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100247 % V: Range without status
Harald Welte661e3812011-03-10 10:22:04 +0100248 RangeLen = binary:at(Bin, PtrVar),
249 Range = binary:part(Bin, PtrVar+1, RangeLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100250 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100251
252
Harald Welte01f8ea32011-01-17 21:30:42 +0100253parse_isup_msg(DataBin) when is_binary(DataBin) ->
254 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100255 Opts = parse_isup_msgt(MsgType, Remain),
256 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100257
258
Harald Welte01f8ea32011-01-17 21:30:42 +0100259% encode a phone number from a list of digits into the BCD binary sequence
Harald Weltec8d06c42011-02-09 22:27:19 +0100260encode_isup_party(BcdInt) when is_integer(BcdInt) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100261 BcdList = osmo_util:int2digit_list(BcdInt),
Harald Weltec8d06c42011-02-09 22:27:19 +0100262 encode_isup_party(BcdList);
263encode_isup_party(BcdList) when is_list(BcdList) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100264 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100265encode_isup_party([], Bin, NumDigits) ->
266 case NumDigits rem 2 of
267 1 ->
268 {Bin, 1};
269 0 ->
270 {Bin, 0}
271 end;
272encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100273 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
274encode_isup_party([Last], Bin, NumDigits) ->
275 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100276
Harald Weltede30a872011-01-16 17:12:56 +0100277% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100278encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100279 #party_number{nature_of_addr_ind = Nature,
280 internal_net_num = Inn,
281 numbering_plan = NumPlan,
282 phone_number= PhoneNum}) ->
283 % C.3.7 Called Party Number
284 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100285 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100286encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100287 #party_number{nature_of_addr_ind = Nature,
288 number_incompl_ind = Ni,
289 numbering_plan = NumPlan,
290 present_restrict = PresRestr,
291 screening_ind = Screen,
292 phone_number= PhoneNum}) ->
293 % C.3.8 Calling Party Number
294 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
295 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100296encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100297 #party_number{nature_of_addr_ind = Nature,
298 numbering_plan = NumPlan,
299 present_restrict = PresRestr,
300 screening_ind = Screen,
301 phone_number = PhoneNum}) ->
302 % C.3.14 Connected Number
303 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
304 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100305encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
306 #party_number{phone_number = PhoneNum}) ->
307 % C.3.32 Subsequent Number
308 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
309 <<OddEven:1, 0:7, PhoneBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100310encode_isup_par(Atom, _More) when is_atom(Atom) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100311 <<>>;
312encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100313 Binary.
314
Harald Welte84cc60d2011-01-18 18:25:53 +0100315% encode a single OPTIONAL parameter (TLV type), skip all others
Harald Weltef48736b2011-01-21 14:34:32 +0100316encode_isup_optpar(ParNum, _ParBody) when is_atom(ParNum) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100317 <<>>;
318encode_isup_optpar(ParNum, ParBody) ->
319 ParBin = encode_isup_par(ParNum, ParBody),
320 ParLen = byte_size(ParBin),
321 <<ParNum:8, ParLen:8, ParBin/binary>>.
322
Harald Weltef48736b2011-01-21 14:34:32 +0100323% recursive function to encode all optional parameters
Harald Welte84cc60d2011-01-18 18:25:53 +0100324encode_isup_opts([], OutBin) ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100325 % terminate with end-of-options, but only if we have options
326 case OutBin of
327 <<>> ->
328 OutBin;
329 _ ->
330 <<OutBin/binary, 0:8>>
331 end;
Harald Welte84cc60d2011-01-18 18:25:53 +0100332encode_isup_opts([Opt|OptPropList], OutBin) ->
333 {OptType, OptBody} = Opt,
334 OptBin = encode_isup_optpar(OptType, OptBody),
335 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
336encode_isup_opts(OptPropList) ->
337 encode_isup_opts(OptPropList, <<>>).
338
339encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
340 <<Cic:12/little, 0:4, MsgType:8>>.
341
Harald Welteed4c9ea2011-01-21 16:58:19 +0000342% Default case: no fixed and no variable parts, only options
343% ANM, RLC, FOT
344encode_isup_msgt(M, #isup_msg{parameters = Params}) when
345 M == ?ISUP_MSGT_ANM;
346 M == ?ISUP_MSGT_RLC;
347 M == ?ISUP_MSGT_FOT ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100348 OptBin = encode_isup_opts(Params),
349 case OptBin of
350 <<>> -> PtrOpt = 0;
351 _ -> PtrOpt = 1
352 end,
353 <<PtrOpt:8, OptBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100354% Table C-5 Address complete
355encode_isup_msgt(?ISUP_MSGT_ACM, #isup_msg{parameters = Params}) ->
356 BackCallInd = proplists:get_value(backward_call_ind, Params),
357 OptBin = encode_isup_opts(Params),
358 case OptBin of
359 <<>> -> PtrOpt = 0;
360 _ -> PtrOpt = 1
361 end,
362 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
363% Table C-7 Call progress
364encode_isup_msgt(?ISUP_MSGT_CPG, #isup_msg{parameters = Params}) ->
365 EventInf = proplists:get_value(event_info, Params),
366 OptBin = encode_isup_opts(Params),
367 case OptBin of
368 <<>> -> PtrOpt = 0;
369 _ -> PtrOpt = 1
370 end,
371 <<EventInf:8, PtrOpt:8, OptBin/binary>>;
372% Table C-9 Circuit group reset acknowledgement
373encode_isup_msgt(?ISUP_MSGT_GRA, #isup_msg{parameters = Params}) ->
374 % V: Range and status
375 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
376 <<1:8, RangStsLen:8, RangeStatus/binary>>;
377% Table C-11 Connect
378encode_isup_msgt(?ISUP_MSGT_CON, #isup_msg{parameters = Params}) ->
379 BackCallInd = proplists:get_value(backward_call_ind, Params),
380 OptBin = encode_isup_opts(Params),
381 case OptBin of
382 <<>> -> PtrOpt = 0;
383 _ -> PtrOpt = 1
384 end,
385 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
386% Table C-12 Continuity
387encode_isup_msgt(?ISUP_MSGT_COT, #isup_msg{parameters = Params}) ->
388 ContInd = proplists:get_value(continuity_ind, Params),
389 <<ContInd:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100390% Table C-16 Initial address
391encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
392 % Fixed part
393 CINat = proplists:get_value(conn_ind_nature, Params),
394 FwCallInd = proplists:get_value(fw_call_ind, Params),
395 CallingCat = proplists:get_value(calling_cat, Params),
396 TransmReq = proplists:get_value(transm_medium_req, Params),
397 PtrVar = 2, % one byte behind the PtrOpt
398 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
399 % V: Called Party Number
400 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
401 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
402 CalledPartyLen = byte_size(CalledParty),
403 % Optional part
Harald Welted1cb16f2011-01-21 15:48:34 +0000404 Params2 = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
405 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100406 case OptBin of
407 <<>> -> PtrOpt = 0;
408 _ -> PtrOpt = CalledPartyLen + 1 + 1 % 1 byte length, 1 byte start offset
409 end,
410 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>;
411% Table C-17 Release
Harald Welte2a91a012011-03-11 16:28:14 +0100412encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when
413 Msgt == ?ISUP_MSGT_REL;
414 Msgt == ?ISUP_MSGT_CFN ->
Harald Weltef48736b2011-01-21 14:34:32 +0100415 PtrVar = 2, % one byte behind the PtrOpt
416 % V: Cause indicators
417 CauseInd = encode_isup_par(?ISUP_PAR_CAUSE_IND,
418 proplists:get_value(?ISUP_PAR_CAUSE_IND, Params)),
419 CauseIndLen = byte_size(CauseInd),
420 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000421 Params2 = proplists:delete(?ISUP_PAR_CAUSE_IND, Params),
422 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100423 case OptBin of
424 <<>> -> PtrOpt = 0;
425 _ -> PtrOpt = CauseIndLen + 1 + 1 % 1 byte length, 1 byte start offset
426 end,
427 <<PtrVar:8, PtrOpt:8, CauseIndLen:8, CauseInd/binary, OptBin/binary>>;
428% Table C-19 Subsequent address
429encode_isup_msgt(?ISUP_MSGT_SAM, #isup_msg{parameters = Params}) ->
430 PtrVar = 2, % one byte behind the PtrOpt
431 % V: Subsequent number
432 SubseqNum = encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
433 proplists:get_value(?ISUP_PAR_SUBSEQ_NUM, Params)),
434 SubseqNumLen = byte_size(SubseqNum),
435 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000436 Params2 = proplists:delete(?ISUP_PAR_SUBSEQ_NUM, Params),
437 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100438 case OptBin of
439 <<>> -> PtrOpt = 0;
440 _ -> PtrOpt = SubseqNumLen + 1 + 1 % 1 byte length, 1 byte start offset
441 end,
442 <<PtrVar:8, PtrOpt:8, SubseqNumLen:8, SubseqNum/binary, OptBin/binary>>;
443% Table C-21 Suspend, Resume
444encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
445 SuspResInd = proplists:get_value(susp_res_ind, Params),
446 OptBin = encode_isup_opts(Params),
447 case OptBin of
448 <<>> -> PtrOpt = 0;
449 _ -> PtrOpt = 1
450 end,
451 <<SuspResInd:8, PtrOpt:8, OptBin/binary>>;
452% Table C-23
453encode_isup_msgt(M, #isup_msg{}) when
454 M == ?ISUP_MSGT_BLO;
455 M == ?ISUP_MSGT_BLA;
456 M == ?ISUP_MSGT_CCR;
457 M == ?ISUP_MSGT_RSC;
458 M == ?ISUP_MSGT_UBL;
459 M == ?ISUP_MSGT_UBA ->
460 <<>>;
Harald Welte2695c3b2011-04-14 11:42:30 +0200461% Table 39/Q.763 (national use)
462encode_isup_msgt(M, #isup_msg{}) when
463 M == ?ISUP_MSGT_LPA;
464 M == ?ISUP_MSGT_OLM;
465 M == ?ISUP_MSGT_UCIC ->
466 <<>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100467% Table C-25
468encode_isup_msgt(M, #isup_msg{parameters = Params}) when
469 M == ?ISUP_MSGT_CGB;
470 M == ?ISUP_MSGT_CGBA;
471 M == ?ISUP_MSGT_CGU;
472 M == ?ISUP_MSGT_CGUA ->
473 PtrVar = 1, % one byte behind the PtrVar
474 CGMsgt = proplists:get_value(cg_supv_msgt, Params),
475 % V: Range and status
476 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
477 <<CGMsgt:8, PtrVar:8, RangStsLen:8, RangeStatus/binary>>;
478% Table C-26 Circuit group reset
479encode_isup_msgt(?ISUP_MSGT_GRS, #isup_msg{parameters = Params}) ->
480 PtrVar = 1, % one byte behind the PtrVar
481 {RangeLen, Range} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
482 % V: Range without status
483 <<PtrVar:8, RangeLen:8, Range/binary>>.
Harald Welte84cc60d2011-01-18 18:25:53 +0100484
485encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
486 HdrBin = encode_isup_hdr(Msg),
487 Remain = encode_isup_msgt(MsgType, Msg),
488 <<HdrBin/binary, Remain/binary>>.
Harald Welte049ee732013-06-24 07:59:52 +0200489
490
491listify(L) when is_list(L) ->
492 L;
493listify(L) when is_integer(L) ->
494 osmo_util:int2digit_list(L).
495
496encode_nature(international) ->
497 ?ISUP_ADDR_NAT_INTERNATIONAL;
498encode_nature(national) ->
499 ?ISUP_ADDR_NAT_NATIONAL;
500encode_nature(subscriber) ->
501 ?ISUP_ADDR_NAT_SUBSCRIBER;
502encode_nature(Int) when is_integer(Int) ->
503 Int.
504
505encode_numplan(isdn) ->
506 1;
507encode_numplan(telephony) ->
508 1;
509encode_numplan(data) ->
510 3;
511encode_numplan(telex) ->
512 4;
513encode_numplan(Int) when is_integer(Int) ->
514 Int.
515
516gen_party_number(NAI, NumPlan, Number) ->
517 #party_number{nature_of_addr_ind = encode_nature(NAI),
518 numbering_plan = encode_numplan(NumPlan),
519 phone_number = listify(Number)}.