blob: 17bf91d807a4b66f32490afa4dfdc40de10bc23d [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 Welte52725272011-04-02 16:48:50 +020028-compile({parse_transform, exprecs}).
29-export_records([party_number, isup_msg]).
30
Harald Weltede30a872011-01-16 17:12:56 +010031parse_isup_party(<<>>, OddEven, DigitList) ->
32 % in case of odd number of digits, we need to cut the last
33 case OddEven of
34 1 ->
Harald Weltec8d06c42011-02-09 22:27:19 +010035 lists:sublist(DigitList, length(DigitList)-1);
Harald Weltede30a872011-01-16 17:12:56 +010036 0 ->
Harald Weltec8d06c42011-02-09 22:27:19 +010037 DigitList
38 end;
Harald Weltede30a872011-01-16 17:12:56 +010039parse_isup_party(BcdBin, OddEven, DigitList) ->
40 <<Second:4, First:4, Remain/binary>> = BcdBin,
41 NewDigits = [First, Second],
42 parse_isup_party(Remain, OddEven, DigitList ++ NewDigits).
43
44parse_isup_party(BinBcd, OddEven) when is_binary(BinBcd) ->
45 parse_isup_party(BinBcd, OddEven, []).
46
47
48% parse a single option
Harald Welte01f8ea32011-01-17 21:30:42 +010049parse_isup_opt(OptType = ?ISUP_PAR_CALLED_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010050 % C.3.7 Called Party Number
51 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, Remain/binary>> = Content,
52 PhoneNum = parse_isup_party(Remain, OddEven),
53 {OptType, #party_number{nature_of_addr_ind = Nature,
54 internal_net_num = Inn,
55 numbering_plan = NumPlan,
56 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010057parse_isup_opt(OptType = ?ISUP_PAR_CALLING_P_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010058 % C.3.8 Calling Party Number
59 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
60 PhoneNum = parse_isup_party(Remain, OddEven),
61 {OptType, #party_number{nature_of_addr_ind = Nature,
62 number_incompl_ind = Ni,
63 numbering_plan = NumPlan,
64 present_restrict = PresRestr,
65 screening_ind = Screen,
66 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010067parse_isup_opt(OptType = ?ISUP_PAR_CONNECTED_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010068 % C.3.14 Connected Number
69 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
70 PhoneNum = parse_isup_party(Remain, OddEven),
71 {OptType, #party_number{nature_of_addr_ind = Nature,
72 numbering_plan = NumPlan,
73 present_restrict = PresRestr,
74 screening_ind = Screen,
75 phone_number = PhoneNum}};
Harald Welte01f8ea32011-01-17 21:30:42 +010076parse_isup_opt(OptType = ?ISUP_PAR_SUBSEQ_NUM, _OptLen, Content) ->
Harald Weltede30a872011-01-16 17:12:56 +010077 % C.3.32 Subsequent Number
Harald Welte01f8ea32011-01-17 21:30:42 +010078 <<OddEven:1, 0:7, Remain/binary>> = Content,
Harald Weltede30a872011-01-16 17:12:56 +010079 PhoneNum = parse_isup_party(Remain, OddEven),
80 {OptType, #party_number{phone_number = PhoneNum}};
81parse_isup_opt(OptType, OptLen, Content) ->
82 {OptType, {OptLen, Content}}.
83
84% parse a Binary into a list of options
85parse_isup_opts(<<>>, OptList) ->
86 % empty list
87 OptList;
88parse_isup_opts(<<0>>, OptList) ->
89 % end of options
90 OptList;
91parse_isup_opts(OptBin, OptList) when is_binary(OptBin) ->
92 <<OptType:8, OptLen:8, Content:OptLen/binary, Remain/binary>> = OptBin,
93 NewOpt = parse_isup_opt(OptType, OptLen, Content),
Harald Welte01f8ea32011-01-17 21:30:42 +010094 parse_isup_opts(Remain, OptList ++ [NewOpt]).
95parse_isup_opts(OptBin) ->
96 parse_isup_opts(OptBin, []).
Harald Weltede30a872011-01-16 17:12:56 +010097
Harald Weltef48736b2011-01-21 14:34:32 +010098% Parse options preceeded by 1 byte OptPtr
99parse_isup_opts_ptr(OptBinPtr) ->
100 OptPtr = binary:at(OptBinPtr, 0),
101 case OptPtr of
102 0 ->
103 [];
104 _ ->
105 OptBin = binary:part(OptBinPtr, OptPtr, byte_size(OptBinPtr)-OptPtr),
106 parse_isup_opts(OptBin, [])
107 end.
108
Harald Welte50a44c22011-01-15 21:39:20 +0100109% References to 'Tabe C-xxx' are to Annex C of Q.767
110
111% Default case: no fixed and no variable parts, only options
112% ANM, RLC, FOT
113parse_isup_msgt(M, Bin) when
114 M == ?ISUP_MSGT_ANM;
115 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +0100116 M == ?ISUP_MSGT_FOT ->
Harald Weltef48736b2011-01-21 14:34:32 +0100117 parse_isup_opts_ptr(Bin);
Harald Welte50a44c22011-01-15 21:39:20 +0100118% Table C-5 Address complete
119parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
120 <<BackCallInd:16, Remain/binary>> = Bin,
121 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100122 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100123 [BciOpt|Opts];
124% Table C-7 Call progress
125parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
126 <<EventInf:8, Remain/binary>> = Bin,
127 BciOpt = {event_info, EventInf},
Harald Weltef48736b2011-01-21 14:34:32 +0100128 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100129 [BciOpt|Opts];
130% Table C-9 Circuit group reset acknowledgement
131parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
132 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100133 <<PtrVar:8, _Remain/binary>> = Bin,
134 RangStsLen = binary:at(Bin, PtrVar),
135 RangeStatus = binary:part(Bin, PtrVar+1, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100136 RangeStsTuple = {?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}},
137 [RangeStsTuple];
Harald Welte50a44c22011-01-15 21:39:20 +0100138% Table C-11 Connect
139parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
140 <<BackCallInd:16, Remain/binary>> = Bin,
141 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltef48736b2011-01-21 14:34:32 +0100142 Opts = parse_isup_opts_ptr(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100143 [BciOpt|Opts];
144% Table C-12 Continuity
145parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
146 <<ContInd:8>> = Bin,
147 [{continuity_ind, ContInd}];
148% Table C-16 Initial address
149parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
150 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
151 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
152 {transm_medium_req, TransmReq}],
Harald Welte01f8ea32011-01-17 21:30:42 +0100153 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100154 % V: Called Party Number
Harald Welte01f8ea32011-01-17 21:30:42 +0100155 CalledPartyLen = binary:at(VarAndOpt, PtrVar),
156 CalledParty = binary:part(VarAndOpt, PtrVar+1, CalledPartyLen),
157 VarOpts = [parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, CalledPartyLen, CalledParty)],
158 % Optional part
Harald Welte86494e82011-01-21 12:13:35 +0000159 case PtrOpt of
160 0 ->
161 Opts = [];
162 _ ->
163 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
164 Opts = parse_isup_opts(Remain)
165 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100166 FixedOpts ++ VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100167% Table C-17 Release
Harald Welte2a91a012011-03-11 16:28:14 +0100168% Table 26/Q.763: Confusion
169parse_isup_msgt(M, VarAndOpt) when
170 M == ?ISUP_MSGT_REL;
171 M == ?ISUP_MSGT_CFN ->
172 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100173 % V: Cause indicators
Harald Welte2a91a012011-03-11 16:28:14 +0100174 CauseIndLen = binary:at(VarAndOpt, PtrVar),
175 CauseInd = binary:part(VarAndOpt, PtrVar+1, CauseIndLen),
Harald Welte86494e82011-01-21 12:13:35 +0000176 VarOpts = [{?ISUP_PAR_CAUSE_IND, {CauseIndLen, CauseInd}}],
177 case PtrOpt of
178 0 ->
179 Opts = [];
180 _ ->
181 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
182 Opts = parse_isup_opts(Remain)
183 end,
Harald Welte01f8ea32011-01-17 21:30:42 +0100184 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100185% Table C-19 Subsequent address
Harald Welte2a91a012011-03-11 16:28:14 +0100186parse_isup_msgt(?ISUP_MSGT_SAM, VarAndOpt) ->
187 <<PtrVar:8, PtrOpt:8, _/binary>> = VarAndOpt,
Harald Welte50a44c22011-01-15 21:39:20 +0100188 % V: Subsequent number
Harald Welte01f8ea32011-01-17 21:30:42 +0100189 SubseqNumLen = binary:at(VarAndOpt, PtrVar),
190 SubsetNum = binary:part(VarAndOpt, PtrVar+1, SubseqNumLen),
191 VarOpts = [{?ISUP_PAR_SUBSEQ_NUM, {SubseqNumLen, SubsetNum}}],
192 Remain = binary:part(VarAndOpt, 1 + PtrOpt, byte_size(VarAndOpt)-(1+PtrOpt)),
Harald Welte50a44c22011-01-15 21:39:20 +0100193 Opts = parse_isup_opts(Remain),
Harald Welte01f8ea32011-01-17 21:30:42 +0100194 VarOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100195% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100196parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100197 <<SuspResInd:8, Remain/binary>> = Bin,
198 FixedOpts = [{susp_res_ind, SuspResInd}],
Harald Weltef48736b2011-01-21 14:34:32 +0100199 Opts = parse_isup_opts_ptr(Remain),
Harald Welte781d98e2011-03-11 16:48:47 +0100200 FixedOpts ++ Opts;
Harald Welte50a44c22011-01-15 21:39:20 +0100201% Table C-23
202parse_isup_msgt(M, <<>>) when
203 M == ?ISUP_MSGT_BLO;
204 M == ?ISUP_MSGT_BLA;
205 M == ?ISUP_MSGT_CCR;
206 M == ?ISUP_MSGT_RSC;
207 M == ?ISUP_MSGT_UBL;
208 M == ?ISUP_MSGT_UBA ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100209 [];
Harald Welte2695c3b2011-04-14 11:42:30 +0200210% Table 39/Q.763 messages for national use, fixed length 1 byte msgtype
211parse_isup_msgt(M, <<>>) when
212 M == ?ISUP_MSGT_LPA;
213 M == ?ISUP_MSGT_OLM;
214 M == ?ISUP_MSGT_UCIC ->
215 [];
Harald Welte50a44c22011-01-15 21:39:20 +0100216% Table C-25
217parse_isup_msgt(M, Bin) when
218 M == ?ISUP_MSGT_CGB;
219 M == ?ISUP_MSGT_CGBA;
Harald Welte01f8ea32011-01-17 21:30:42 +0100220 M == ?ISUP_MSGT_CGU;
221 M == ?ISUP_MSGT_CGUA ->
222 <<CGMsgt:8, PtrVar:8, VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100223 FixedOpts = [{cg_supv_msgt, CGMsgt}],
224 % V: Range and status
Harald Welte661e3812011-03-10 10:22:04 +0100225 RangStsLen = binary:at(VarBin, PtrVar-1),
226 RangeStatus = binary:part(VarBin, PtrVar, RangStsLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100227 VarOpts = [{?ISUP_PAR_RANGE_AND_STATUS, {RangStsLen, RangeStatus}}],
228 FixedOpts ++ VarOpts;
Harald Welte50a44c22011-01-15 21:39:20 +0100229% Table C-26 Circuit group reset
230parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
Harald Welte661e3812011-03-10 10:22:04 +0100231 <<PtrVar:8, _VarBin/binary>> = Bin,
Harald Welte50a44c22011-01-15 21:39:20 +0100232 % V: Range without status
Harald Welte661e3812011-03-10 10:22:04 +0100233 RangeLen = binary:at(Bin, PtrVar),
234 Range = binary:part(Bin, PtrVar+1, RangeLen),
Harald Welte01f8ea32011-01-17 21:30:42 +0100235 [{?ISUP_PAR_RANGE_AND_STATUS, {RangeLen, Range}}].
Harald Welte50a44c22011-01-15 21:39:20 +0100236
237
Harald Welte01f8ea32011-01-17 21:30:42 +0100238parse_isup_msg(DataBin) when is_binary(DataBin) ->
239 <<Cic:12/little, 0:4, MsgType:8, Remain/binary>> = DataBin,
Harald Welte50a44c22011-01-15 21:39:20 +0100240 Opts = parse_isup_msgt(MsgType, Remain),
241 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100242
243
Harald Welte01f8ea32011-01-17 21:30:42 +0100244% encode a phone number from a list of digits into the BCD binary sequence
Harald Weltec8d06c42011-02-09 22:27:19 +0100245encode_isup_party(BcdInt) when is_integer(BcdInt) ->
Harald Welte93b2ab52011-02-06 21:48:58 +0100246 BcdList = osmo_util:int2digit_list(BcdInt),
Harald Weltec8d06c42011-02-09 22:27:19 +0100247 encode_isup_party(BcdList);
248encode_isup_party(BcdList) when is_list(BcdList) ->
Harald Welte01f8ea32011-01-17 21:30:42 +0100249 encode_isup_party(BcdList, <<>>, length(BcdList)).
Harald Weltede30a872011-01-16 17:12:56 +0100250encode_isup_party([], Bin, NumDigits) ->
251 case NumDigits rem 2 of
252 1 ->
253 {Bin, 1};
254 0 ->
255 {Bin, 0}
256 end;
257encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100258 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>, NumDigits);
259encode_isup_party([Last], Bin, NumDigits) ->
260 encode_isup_party([], <<Bin/binary, 0:4, Last:4>>, NumDigits).
Harald Welte01f8ea32011-01-17 21:30:42 +0100261
Harald Weltede30a872011-01-16 17:12:56 +0100262% encode a single option
Harald Welte84cc60d2011-01-18 18:25:53 +0100263encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100264 #party_number{nature_of_addr_ind = Nature,
265 internal_net_num = Inn,
266 numbering_plan = NumPlan,
267 phone_number= PhoneNum}) ->
268 % C.3.7 Called Party Number
269 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
Harald Welte01f8ea32011-01-17 21:30:42 +0100270 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100271encode_isup_par(?ISUP_PAR_CALLING_P_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100272 #party_number{nature_of_addr_ind = Nature,
273 number_incompl_ind = Ni,
274 numbering_plan = NumPlan,
275 present_restrict = PresRestr,
276 screening_ind = Screen,
277 phone_number= PhoneNum}) ->
278 % C.3.8 Calling Party Number
279 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
280 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100281encode_isup_par(?ISUP_PAR_CONNECTED_NUM,
Harald Weltede30a872011-01-16 17:12:56 +0100282 #party_number{nature_of_addr_ind = Nature,
283 numbering_plan = NumPlan,
284 present_restrict = PresRestr,
285 screening_ind = Screen,
286 phone_number = PhoneNum}) ->
287 % C.3.14 Connected Number
288 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
289 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100290encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
291 #party_number{phone_number = PhoneNum}) ->
292 % C.3.32 Subsequent Number
293 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
294 <<OddEven:1, 0:7, PhoneBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100295encode_isup_par(Atom, _More) when is_atom(Atom) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100296 <<>>;
297encode_isup_par(OptNum, {OptLen, Binary}) when is_binary(Binary), is_integer(OptNum), is_integer(OptLen) ->
Harald Weltede30a872011-01-16 17:12:56 +0100298 Binary.
299
Harald Welte84cc60d2011-01-18 18:25:53 +0100300% encode a single OPTIONAL parameter (TLV type), skip all others
Harald Weltef48736b2011-01-21 14:34:32 +0100301encode_isup_optpar(ParNum, _ParBody) when is_atom(ParNum) ->
Harald Welte84cc60d2011-01-18 18:25:53 +0100302 <<>>;
303encode_isup_optpar(ParNum, ParBody) ->
304 ParBin = encode_isup_par(ParNum, ParBody),
305 ParLen = byte_size(ParBin),
306 <<ParNum:8, ParLen:8, ParBin/binary>>.
307
Harald Weltef48736b2011-01-21 14:34:32 +0100308% recursive function to encode all optional parameters
Harald Welte84cc60d2011-01-18 18:25:53 +0100309encode_isup_opts([], OutBin) ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100310 % terminate with end-of-options, but only if we have options
311 case OutBin of
312 <<>> ->
313 OutBin;
314 _ ->
315 <<OutBin/binary, 0:8>>
316 end;
Harald Welte84cc60d2011-01-18 18:25:53 +0100317encode_isup_opts([Opt|OptPropList], OutBin) ->
318 {OptType, OptBody} = Opt,
319 OptBin = encode_isup_optpar(OptType, OptBody),
320 encode_isup_opts(OptPropList, <<OutBin/binary, OptBin/binary>>).
321encode_isup_opts(OptPropList) ->
322 encode_isup_opts(OptPropList, <<>>).
323
324encode_isup_hdr(#isup_msg{msg_type = MsgType, cic = Cic}) ->
325 <<Cic:12/little, 0:4, MsgType:8>>.
326
Harald Welteed4c9ea2011-01-21 16:58:19 +0000327% Default case: no fixed and no variable parts, only options
328% ANM, RLC, FOT
329encode_isup_msgt(M, #isup_msg{parameters = Params}) when
330 M == ?ISUP_MSGT_ANM;
331 M == ?ISUP_MSGT_RLC;
332 M == ?ISUP_MSGT_FOT ->
Harald Welte39eae2d2011-03-11 16:46:09 +0100333 OptBin = encode_isup_opts(Params),
334 case OptBin of
335 <<>> -> PtrOpt = 0;
336 _ -> PtrOpt = 1
337 end,
338 <<PtrOpt:8, OptBin/binary>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100339% Table C-5 Address complete
340encode_isup_msgt(?ISUP_MSGT_ACM, #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-7 Call progress
349encode_isup_msgt(?ISUP_MSGT_CPG, #isup_msg{parameters = Params}) ->
350 EventInf = proplists:get_value(event_info, Params),
351 OptBin = encode_isup_opts(Params),
352 case OptBin of
353 <<>> -> PtrOpt = 0;
354 _ -> PtrOpt = 1
355 end,
356 <<EventInf:8, PtrOpt:8, OptBin/binary>>;
357% Table C-9 Circuit group reset acknowledgement
358encode_isup_msgt(?ISUP_MSGT_GRA, #isup_msg{parameters = Params}) ->
359 % V: Range and status
360 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
361 <<1:8, RangStsLen:8, RangeStatus/binary>>;
362% Table C-11 Connect
363encode_isup_msgt(?ISUP_MSGT_CON, #isup_msg{parameters = Params}) ->
364 BackCallInd = proplists:get_value(backward_call_ind, Params),
365 OptBin = encode_isup_opts(Params),
366 case OptBin of
367 <<>> -> PtrOpt = 0;
368 _ -> PtrOpt = 1
369 end,
370 <<BackCallInd:16, PtrOpt:8, OptBin/binary>>;
371% Table C-12 Continuity
372encode_isup_msgt(?ISUP_MSGT_COT, #isup_msg{parameters = Params}) ->
373 ContInd = proplists:get_value(continuity_ind, Params),
374 <<ContInd:8>>;
Harald Welte84cc60d2011-01-18 18:25:53 +0100375% Table C-16 Initial address
376encode_isup_msgt(?ISUP_MSGT_IAM, #isup_msg{parameters = Params}) ->
377 % Fixed part
378 CINat = proplists:get_value(conn_ind_nature, Params),
379 FwCallInd = proplists:get_value(fw_call_ind, Params),
380 CallingCat = proplists:get_value(calling_cat, Params),
381 TransmReq = proplists:get_value(transm_medium_req, Params),
382 PtrVar = 2, % one byte behind the PtrOpt
383 FixedBin = <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8>>,
384 % V: Called Party Number
385 CalledParty = encode_isup_par(?ISUP_PAR_CALLED_P_NUM,
386 proplists:get_value(?ISUP_PAR_CALLED_P_NUM, Params)),
387 CalledPartyLen = byte_size(CalledParty),
388 % Optional part
Harald Welted1cb16f2011-01-21 15:48:34 +0000389 Params2 = proplists:delete(?ISUP_PAR_CALLED_P_NUM, Params),
390 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100391 case OptBin of
392 <<>> -> PtrOpt = 0;
393 _ -> PtrOpt = CalledPartyLen + 1 + 1 % 1 byte length, 1 byte start offset
394 end,
395 <<FixedBin/binary, PtrVar:8, PtrOpt:8, CalledPartyLen:8, CalledParty/binary, OptBin/binary>>;
396% Table C-17 Release
Harald Welte2a91a012011-03-11 16:28:14 +0100397encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when
398 Msgt == ?ISUP_MSGT_REL;
399 Msgt == ?ISUP_MSGT_CFN ->
Harald Weltef48736b2011-01-21 14:34:32 +0100400 PtrVar = 2, % one byte behind the PtrOpt
401 % V: Cause indicators
402 CauseInd = encode_isup_par(?ISUP_PAR_CAUSE_IND,
403 proplists:get_value(?ISUP_PAR_CAUSE_IND, Params)),
404 CauseIndLen = byte_size(CauseInd),
405 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000406 Params2 = proplists:delete(?ISUP_PAR_CAUSE_IND, Params),
407 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100408 case OptBin of
409 <<>> -> PtrOpt = 0;
410 _ -> PtrOpt = CauseIndLen + 1 + 1 % 1 byte length, 1 byte start offset
411 end,
412 <<PtrVar:8, PtrOpt:8, CauseIndLen:8, CauseInd/binary, OptBin/binary>>;
413% Table C-19 Subsequent address
414encode_isup_msgt(?ISUP_MSGT_SAM, #isup_msg{parameters = Params}) ->
415 PtrVar = 2, % one byte behind the PtrOpt
416 % V: Subsequent number
417 SubseqNum = encode_isup_par(?ISUP_PAR_SUBSEQ_NUM,
418 proplists:get_value(?ISUP_PAR_SUBSEQ_NUM, Params)),
419 SubseqNumLen = byte_size(SubseqNum),
420 % Optional Part
Harald Welted1cb16f2011-01-21 15:48:34 +0000421 Params2 = proplists:delete(?ISUP_PAR_SUBSEQ_NUM, Params),
422 OptBin = encode_isup_opts(Params2),
Harald Weltef48736b2011-01-21 14:34:32 +0100423 case OptBin of
424 <<>> -> PtrOpt = 0;
425 _ -> PtrOpt = SubseqNumLen + 1 + 1 % 1 byte length, 1 byte start offset
426 end,
427 <<PtrVar:8, PtrOpt:8, SubseqNumLen:8, SubseqNum/binary, OptBin/binary>>;
428% Table C-21 Suspend, Resume
429encode_isup_msgt(Msgt, #isup_msg{parameters = Params}) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
430 SuspResInd = proplists:get_value(susp_res_ind, Params),
431 OptBin = encode_isup_opts(Params),
432 case OptBin of
433 <<>> -> PtrOpt = 0;
434 _ -> PtrOpt = 1
435 end,
436 <<SuspResInd:8, PtrOpt:8, OptBin/binary>>;
437% Table C-23
438encode_isup_msgt(M, #isup_msg{}) when
439 M == ?ISUP_MSGT_BLO;
440 M == ?ISUP_MSGT_BLA;
441 M == ?ISUP_MSGT_CCR;
442 M == ?ISUP_MSGT_RSC;
443 M == ?ISUP_MSGT_UBL;
444 M == ?ISUP_MSGT_UBA ->
445 <<>>;
Harald Welte2695c3b2011-04-14 11:42:30 +0200446% Table 39/Q.763 (national use)
447encode_isup_msgt(M, #isup_msg{}) when
448 M == ?ISUP_MSGT_LPA;
449 M == ?ISUP_MSGT_OLM;
450 M == ?ISUP_MSGT_UCIC ->
451 <<>>;
Harald Weltef48736b2011-01-21 14:34:32 +0100452% Table C-25
453encode_isup_msgt(M, #isup_msg{parameters = Params}) when
454 M == ?ISUP_MSGT_CGB;
455 M == ?ISUP_MSGT_CGBA;
456 M == ?ISUP_MSGT_CGU;
457 M == ?ISUP_MSGT_CGUA ->
458 PtrVar = 1, % one byte behind the PtrVar
459 CGMsgt = proplists:get_value(cg_supv_msgt, Params),
460 % V: Range and status
461 {RangStsLen, RangeStatus} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
462 <<CGMsgt:8, PtrVar:8, RangStsLen:8, RangeStatus/binary>>;
463% Table C-26 Circuit group reset
464encode_isup_msgt(?ISUP_MSGT_GRS, #isup_msg{parameters = Params}) ->
465 PtrVar = 1, % one byte behind the PtrVar
466 {RangeLen, Range} = proplists:get_value(?ISUP_PAR_RANGE_AND_STATUS, Params),
467 % V: Range without status
468 <<PtrVar:8, RangeLen:8, Range/binary>>.
Harald Welte84cc60d2011-01-18 18:25:53 +0100469
470encode_isup_msg(Msg = #isup_msg{msg_type = MsgType}) ->
471 HdrBin = encode_isup_hdr(Msg),
472 Remain = encode_isup_msgt(MsgType, Msg),
473 <<HdrBin/binary, Remain/binary>>.