blob: a98da3144519915f88fa402273f5afa6c2275117 [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
24-export([parse_isup_msg/1, encode_isup_msg/1]).
25
Harald Weltede30a872011-01-16 17:12:56 +010026parse_isup_party(<<>>, OddEven, DigitList) ->
27 % in case of odd number of digits, we need to cut the last
28 case OddEven of
29 1 ->
30 lists:sublist(DigitList, lists:length(DigitList)-1);
31 0 ->
32 DigitList
33 end;
34parse_isup_party(BcdBin, OddEven, DigitList) ->
35 <<Second:4, First:4, Remain/binary>> = BcdBin,
36 NewDigits = [First, Second],
37 parse_isup_party(Remain, OddEven, DigitList ++ NewDigits).
38
39parse_isup_party(BinBcd, OddEven) when is_binary(BinBcd) ->
40 parse_isup_party(BinBcd, OddEven, []).
41
42
43% parse a single option
44parse_isup_opt(?ISUP_PAR_CALLED_P_NUM, OptLen, Content) ->
45 % C.3.7 Called Party Number
46 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, Remain/binary>> = Content,
47 PhoneNum = parse_isup_party(Remain, OddEven),
48 {OptType, #party_number{nature_of_addr_ind = Nature,
49 internal_net_num = Inn,
50 numbering_plan = NumPlan,
51 phone_number = PhoneNum}};
52parse_isup_opt(?ISUP_PAR_CALLING_P_NUM, OptLen, Content) ->
53 % C.3.8 Calling Party Number
54 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
55 PhoneNum = parse_isup_party(Remain, OddEven),
56 {OptType, #party_number{nature_of_addr_ind = Nature,
57 number_incompl_ind = Ni,
58 numbering_plan = NumPlan,
59 present_restrict = PresRestr,
60 screening_ind = Screen,
61 phone_number = PhoneNum}};
62parse_isup_opt(?ISUP_PAR_CONNECTED_NUM, OptLen, Content) ->
63 % C.3.14 Connected Number
64 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, Remain/binary>> = Content,
65 PhoneNum = parse_isup_party(Remain, OddEven),
66 {OptType, #party_number{nature_of_addr_ind = Nature,
67 numbering_plan = NumPlan,
68 present_restrict = PresRestr,
69 screening_ind = Screen,
70 phone_number = PhoneNum}};
71parse_isup_opt(?ISUP_PAR_SUBSEQ_NUM, OptLen, Content) ->
72 % C.3.32 Subsequent Number
73 <<OddEven:1, Spare:7, Remain/binary>> = Content,
74 PhoneNum = parse_isup_party(Remain, OddEven),
75 {OptType, #party_number{phone_number = PhoneNum}};
76parse_isup_opt(OptType, OptLen, Content) ->
77 {OptType, {OptLen, Content}}.
78
79% parse a Binary into a list of options
80parse_isup_opts(<<>>, OptList) ->
81 % empty list
82 OptList;
83parse_isup_opts(<<0>>, OptList) ->
84 % end of options
85 OptList;
86parse_isup_opts(OptBin, OptList) when is_binary(OptBin) ->
87 <<OptType:8, OptLen:8, Content:OptLen/binary, Remain/binary>> = OptBin,
88 NewOpt = parse_isup_opt(OptType, OptLen, Content),
89 parse_isup_opts(Remain, [NewOpt|OptList]).
90
Harald Welte50a44c22011-01-15 21:39:20 +010091% References to 'Tabe C-xxx' are to Annex C of Q.767
92
93% Default case: no fixed and no variable parts, only options
94% ANM, RLC, FOT
95parse_isup_msgt(M, Bin) when
96 M == ?ISUP_MSGT_ANM;
97 M == ?ISUP_MSGT_RLC;
Harald Weltede30a872011-01-16 17:12:56 +010098 M == ?ISUP_MSGT_FOT ->
Harald Welte50a44c22011-01-15 21:39:20 +010099 parse_isup_opts(Bin);
100% Table C-5 Address complete
101parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
102 <<BackCallInd:16, Remain/binary>> = Bin,
103 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltede30a872011-01-16 17:12:56 +0100104 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100105 [BciOpt|Opts];
106% Table C-7 Call progress
107parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
108 <<EventInf:8, Remain/binary>> = Bin,
109 BciOpt = {event_info, EventInf},
Harald Weltede30a872011-01-16 17:12:56 +0100110 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100111 [BciOpt|Opts];
112% Table C-9 Circuit group reset acknowledgement
113parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
114 % V: Range and status
Harald Weltede30a872011-01-16 17:12:56 +0100115 0;
Harald Welte50a44c22011-01-15 21:39:20 +0100116% Table C-11 Connect
117parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
118 <<BackCallInd:16, Remain/binary>> = Bin,
119 BciOpt = {backward_call_ind, BackCallInd},
Harald Weltede30a872011-01-16 17:12:56 +0100120 Opts = parse_isup_opts(Remain),
Harald Welte50a44c22011-01-15 21:39:20 +0100121 [BciOpt|Opts];
122% Table C-12 Continuity
123parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
124 <<ContInd:8>> = Bin,
125 [{continuity_ind, ContInd}];
126% Table C-16 Initial address
127parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
128 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
129 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
130 {transm_medium_req, TransmReq}],
131 % V: Called Party Number
Harald Weltede30a872011-01-16 17:12:56 +0100132 VarOpts = FIXME,
Harald Welte50a44c22011-01-15 21:39:20 +0100133 Opts = parse_isup_opts(Remain),
134 [FixedOpts,VarOpts,Opts];
135% Table C-17 Release
136parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
137 % V: Cause indicators
Harald Weltede30a872011-01-16 17:12:56 +0100138 VarOpts = FIXME,
Harald Welte50a44c22011-01-15 21:39:20 +0100139 Opts = parse_isup_opts(Remain),
140 [VarOpts,Opts];
141% Table C-19 Subsequent address
142parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
143 % V: Subsequent number
Harald Weltede30a872011-01-16 17:12:56 +0100144 VarOpts = FIXME,
Harald Welte50a44c22011-01-15 21:39:20 +0100145 Opts = parse_isup_opts(Remain),
146 [VarOpts,Opts];
147% Table C-21 Suspend, Resume
Harald Weltede30a872011-01-16 17:12:56 +0100148parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES; Msgt == ?ISUP_MSGT_SUS ->
Harald Welte50a44c22011-01-15 21:39:20 +0100149 <<SuspResInd:8, Remain/binary>> = Bin,
150 FixedOpts = [{susp_res_ind, SuspResInd}],
151 Opts = parse_isup_opts(Remain),
152 [FixedOpts|Opts];
153% Table C-23
154parse_isup_msgt(M, <<>>) when
155 M == ?ISUP_MSGT_BLO;
156 M == ?ISUP_MSGT_BLA;
157 M == ?ISUP_MSGT_CCR;
158 M == ?ISUP_MSGT_RSC;
159 M == ?ISUP_MSGT_UBL;
160 M == ?ISUP_MSGT_UBA ->
161 [].
162% Table C-25
163parse_isup_msgt(M, Bin) when
164 M == ?ISUP_MSGT_CGB;
165 M == ?ISUP_MSGT_CGBA;
166 M == ISUP_MSGT_CGU;
167 M == ISUP_MSGT_CGUA ->
168 <<CGMsgt:8, VarBin/binary>> = Bin,
169 FixedOpts = [{cg_supv_msgt, CGMsgt}],
170 % V: Range and status
171 VarOpts = FIXME,
172 [FixedOpts|VarOpts];
173% Table C-26 Circuit group reset
174parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
175 % V: Range without status
176 VarOpts = FIXME,
177 VarOpts.
178
179
180parse_isup_msg(Databin) when is_binary(DataBin) ->
181 <<0:4, Cic:12/big, MsgType:8, Remain/binary>> = DataBin,
182 Opts = parse_isup_msgt(MsgType, Remain),
183 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.
Harald Weltede30a872011-01-16 17:12:56 +0100184
185
186encode_isup_party(BcdList) ->
187 encode_isup_party(BcdList, <<>>, list:length(BcdList)).
188encode_isup_party([], Bin, NumDigits) ->
189 case NumDigits rem 2 of
190 1 ->
191 {Bin, 1};
192 0 ->
193 {Bin, 0}
194 end;
195encode_isup_party([First,Second|BcdList], Bin, NumDigits) ->
196 encode_isup_party(BcdList, <<Bin/binary, Second:4, First:4>>).
197
198% encode a single option
199encode_isup_opt(?ISUP_PAR_CALLED_P_NUM,
200 #party_number{nature_of_addr_ind = Nature,
201 internal_net_num = Inn,
202 numbering_plan = NumPlan,
203 phone_number= PhoneNum}) ->
204 % C.3.7 Called Party Number
205 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
206 <<OddEven:1, Nature:7, Inn:1, NumPlan:3, 0:4, PhoneBin/binary>>.
207encode_isup_opt(?ISUP_PAR_CALLING_P_NUM,
208 #party_number{nature_of_addr_ind = Nature,
209 number_incompl_ind = Ni,
210 numbering_plan = NumPlan,
211 present_restrict = PresRestr,
212 screening_ind = Screen,
213 phone_number= PhoneNum}) ->
214 % C.3.8 Calling Party Number
215 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
216 <<OddEven:1, Nature:7, Ni:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
217encode_isup_opt(?ISUP_PAR_CONNECTED_NUM,
218 #party_number{nature_of_addr_ind = Nature,
219 numbering_plan = NumPlan,
220 present_restrict = PresRestr,
221 screening_ind = Screen,
222 phone_number = PhoneNum}) ->
223 % C.3.14 Connected Number
224 {PhoneBin, OddEven} = encode_isup_party(PhoneNum),
225 <<OddEven:1, Nature:7, 0:1, NumPlan:3, PresRestr:2, Screen:2, PhoneBin/binary>>;
226encode_isup_opt(OptNum, {OptLen, Binary}) when is_binary(Binary) ->
227 Binary.
228