blob: 2374d736a7d2484b1efda39e44457045834e378e [file] [log] [blame]
Harald Welte033cef02010-12-19 22:47:14 +01001% ITU-T Q.71x SCCP Message coding / decoding
2
3% (C) 2010 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 Welte033cef02010-12-19 22:47:14 +010033
34-module(sccp_codec).
35-author('Harald Welte <laforge@gnumonks.org>').
36-include("sccp.hrl").
37
Harald Welte9abbbad2011-04-21 12:19:41 +020038-export([parse_sccp_msg/1, encode_sccp_msg/1, encode_sccp_msgt/2,
39 is_connectionless/1]).
Harald Welte033cef02010-12-19 22:47:14 +010040
Harald Welte9baab6d2011-12-08 00:46:00 +010041-export([gen_gt_helper/1, gen_addr_helper/2, gen_addr_helper/3]).
42
Harald Welte033cef02010-12-19 22:47:14 +010043-compile(export_all).
44
Harald Welte2edaf552011-04-02 16:46:16 +020045-compile({parse_transform, exprecs}).
Harald Welte0f2f5962011-04-04 15:59:49 +020046-export_records([global_title, sccp_addr, sccp_msg]).
Harald Welte2edaf552011-04-02 16:46:16 +020047
Harald Welted9c318f2011-12-10 22:17:11 +010048binarify(In) when is_binary(In) ->
49 In;
50binarify(In) when is_list(In) ->
51 list_to_binary(In).
52
Harald Welte2b4b2672011-02-03 12:50:41 +010053parse_point_code(BinPC, PCind) when is_binary(BinPC) ->
Harald Welteba6fdbb2011-01-23 22:04:39 +010054 case PCind of
55 1 ->
Harald Welte9c3b1bb2011-10-12 17:00:34 +020056 <<PointCode:16/little, Remain/binary>> = BinPC;
Harald Welteba6fdbb2011-01-23 22:04:39 +010057 _ ->
58 Remain = BinPC,
Harald Welteb5936ba2011-12-08 00:58:51 +010059 PointCode = undefined
Harald Welteba6fdbb2011-01-23 22:04:39 +010060 end,
Harald Welte2b4b2672011-02-03 12:50:41 +010061 {Remain, PointCode}.
Harald Welteba6fdbb2011-01-23 22:04:39 +010062
Harald Welte2b4b2672011-02-03 12:50:41 +010063parse_ssn(BinSSN, SSNind) ->
Harald Welteba6fdbb2011-01-23 22:04:39 +010064 case SSNind of
65 1 ->
Harald Welte2b4b2672011-02-03 12:50:41 +010066 <<SSN:8, Remain/binary>> = BinSSN;
Harald Welteba6fdbb2011-01-23 22:04:39 +010067 _ ->
68 Remain = BinSSN,
Harald Welteb5936ba2011-12-08 00:58:51 +010069 SSN = undefined
Harald Welteba6fdbb2011-01-23 22:04:39 +010070 end,
Harald Welte2b4b2672011-02-03 12:50:41 +010071 {Remain, SSN}.
Harald Welteba6fdbb2011-01-23 22:04:39 +010072
73enc_is_odd(Enc) ->
74 case Enc of
75 1 -> 1;
76 _ -> 0
77 end.
78
Harald Welte2b4b2672011-02-03 12:50:41 +010079parse_gt(BinGT, GTind) ->
Harald Welteba6fdbb2011-01-23 22:04:39 +010080 case GTind of
81 ?SCCP_GTI_NO_GT ->
Harald Welteb5936ba2011-12-08 00:58:51 +010082 undefined;
Harald Welteba6fdbb2011-01-23 22:04:39 +010083 ?SCCP_GTI_NAT_ONLY ->
84 % Figure 7/Q.713
85 <<Odd:1, Nature:7, Digits/binary>> = BinGT,
86 PhoneNum = isup_codec:parse_isup_party(Digits, Odd),
Harald Welte2b4b2672011-02-03 12:50:41 +010087 #global_title{gti = GTind,
88 nature_of_addr_ind = Nature,
89 phone_number = PhoneNum};
Harald Welteba6fdbb2011-01-23 22:04:39 +010090 ?SCCP_GTI_TT_ONLY ->
91 % Figure 9/Q.913
92 <<TransType:8, Digits/binary>> = BinGT,
93 % Used in national interfaces only, we cannot parse Digits
Harald Welte2b4b2672011-02-03 12:50:41 +010094 #global_title{gti = GTind,
95 trans_type = TransType,
96 phone_number = Digits};
Harald Welteba6fdbb2011-01-23 22:04:39 +010097 ?SCCP_GTI_TT_NP_ENC ->
98 % Figure 10/Q.713
99 <<TransType:8, NumPlan:4, Enc:4, Digits/binary>> = BinGT,
100 PhoneNum = isup_codec:parse_isup_party(Digits, enc_is_odd(Enc)),
Harald Welte2b4b2672011-02-03 12:50:41 +0100101 #global_title{gti = GTind,
Harald Welte2c67ac02012-01-18 08:49:45 +0100102 trans_type = TransType,
Harald Welte2b4b2672011-02-03 12:50:41 +0100103 numbering_plan = NumPlan,
104 phone_number = PhoneNum};
Harald Welteba6fdbb2011-01-23 22:04:39 +0100105 ?SCCP_GTI_TT_NP_ENC_NAT ->
106 % Figure 11/Q.713
107 <<TransType:8, NumPlan:4, Enc:4, 0:1, Nature:7, Digits/binary>> = BinGT,
108 PhoneNum = isup_codec:parse_isup_party(Digits, enc_is_odd(Enc)),
Harald Welte2b4b2672011-02-03 12:50:41 +0100109 #global_title{gti = GTind,
Harald Welte2c67ac02012-01-18 08:49:45 +0100110 trans_type = TransType,
Harald Welte2b4b2672011-02-03 12:50:41 +0100111 numbering_plan = NumPlan,
112 nature_of_addr_ind = Nature,
113 phone_number = PhoneNum};
Harald Welteba6fdbb2011-01-23 22:04:39 +0100114 _ ->
Harald Welte2b4b2672011-02-03 12:50:41 +0100115 BinGT
116 end.
Harald Welteba6fdbb2011-01-23 22:04:39 +0100117
118% parse SCCP Address
119parse_sccp_addr(BinAddr) when is_binary(BinAddr) ->
120 <<ResNatUse:1, RoutInd:1, GTind:4, SSNind:1, PCind:1, Remain/binary>> = BinAddr,
Harald Welte2b4b2672011-02-03 12:50:41 +0100121 {RemainPC, OptPC} = parse_point_code(Remain, PCind),
122 {RemainSSN, OptSSN} = parse_ssn(RemainPC, SSNind),
123 OptGT = parse_gt(RemainSSN, GTind),
124 #sccp_addr{res_nat_use = ResNatUse, route_on_ssn = RoutInd,
125 point_code = OptPC, ssn = OptSSN, global_title = OptGT}.
Harald Welte033cef02010-12-19 22:47:14 +0100126
127% parse SCCP Optional Part
Harald Welte9dda4e12012-01-23 16:15:06 +0100128parse_sccp_opt(OptType, _OptLen, Content) ->
129 OptAtom = opt_to_atom(OptType),
130 {OptAtom, Content}.
Harald Welte033cef02010-12-19 22:47:14 +0100131
132parse_sccp_opts(<<>>, OptList) ->
133 % empty list
134 OptList;
135parse_sccp_opts(<<0>>, OptList) ->
136 % end of options
137 OptList;
138parse_sccp_opts(OptBin, OptList) ->
139 <<OptType, OptLen, Content:OptLen/binary, Remain/binary>> = OptBin,
140 NewOpt = parse_sccp_opt(OptType, OptLen, Content),
141 parse_sccp_opts(Remain, [NewOpt|OptList]).
142
Harald Welte9dda4e12012-01-23 16:15:06 +0100143
Harald Welte033cef02010-12-19 22:47:14 +0100144% Parse incoming SCCP message, one function for every message type
145parse_sccp_msgt(?SCCP_MSGT_CR, DataBin) ->
146 % first get the fixed part
Harald Welte11565772011-04-15 10:37:57 +0200147 <<_:8, SrcLocalRef:24/big, PCOpt:4, ProtoClass:4, RemainVar/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100148 % variable length fixed part
149 <<PtrVar:8, PtrOpt:8, _/binary>> = RemainVar,
150 CalledPartyLen = binary:at(RemainVar, PtrVar),
151 CalledParty = binary:part(RemainVar, PtrVar+1, CalledPartyLen),
Harald Welte234c9562011-02-03 13:51:12 +0100152 CalledPartyDec = parse_sccp_addr(CalledParty),
Harald Welte033cef02010-12-19 22:47:14 +0100153 % optional part
154 OptBin = binary:part(RemainVar, 1 + PtrOpt, byte_size(RemainVar)-(1+PtrOpt)),
155 OptList = parse_sccp_opts(OptBin, []),
156 %OptList = [],
157 % build parsed list of message
Harald Welte11565772011-04-15 10:37:57 +0200158 [{src_local_ref, SrcLocalRef},{protocol_class, {ProtoClass, PCOpt}},
159 {called_party_addr, CalledPartyDec} | OptList];
Harald Welte033cef02010-12-19 22:47:14 +0100160parse_sccp_msgt(?SCCP_MSGT_CC, DataBin) ->
161 % first get the fixed part
Harald Weltecbddf842012-01-24 22:58:01 +0100162 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big, PCOpt:4, ProtoClass:4, PtrOpt:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100163 % optional part
Harald Weltecbddf842012-01-24 22:58:01 +0100164 OptBin = binary:part(Remain, PtrOpt-1, byte_size(Remain)-(PtrOpt-1)),
165 OptList = parse_sccp_opts(OptBin, []),
Harald Welte033cef02010-12-19 22:47:14 +0100166 % build parsed list of message
Harald Welte11565772011-04-15 10:37:57 +0200167 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},
168 {protocol_class, {ProtoClass, PCOpt}} | OptList];
Harald Welte033cef02010-12-19 22:47:14 +0100169parse_sccp_msgt(?SCCP_MSGT_CREF, DataBin) ->
170 % first get the fixed part
Harald Welte56ee7a62010-12-20 13:34:32 +0100171 <<_:8, DstLocalRef:24/big, RefusalCause:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100172 % optional part
173 OptList = parse_sccp_opts(Remain, []),
174 % build parsed list of message
175 [{dst_local_ref, DstLocalRef},{refusal_cause, RefusalCause}|OptList];
176parse_sccp_msgt(?SCCP_MSGT_RLSD, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100177 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big, ReleaseCause:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100178 % optional part
179 OptList = parse_sccp_opts(Remain, []),
180 % build parsed list of message
181 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},{release_cause, ReleaseCause}|OptList];
182parse_sccp_msgt(?SCCP_MSGT_RLC, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100183 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100184 % build parsed list of message
185 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef}];
186parse_sccp_msgt(?SCCP_MSGT_DT1, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100187 <<_:8, DstLocalRef:24/big, SegmReass:8, DataPtr:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100188 DataLen = binary:at(Remain, DataPtr-1),
189 UserData = binary:part(Remain, DataPtr-1+1, DataLen),
190 % build parsed list of message
191 [{dst_local_ref, DstLocalRef},{segm_reass, SegmReass},{user_data, UserData}];
192parse_sccp_msgt(?SCCP_MSGT_DT2, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100193 <<_:8, DstLocalRef:24/big, SeqSegm:16, DataPtr:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100194 DataLen = binary:at(Remain, DataPtr-1),
195 UserData = binary:part(Remain, DataPtr-1+1, DataLen),
196 % build parsed list of message
197 [{dst_local_ref, DstLocalRef},{seq_segm, SeqSegm},{user_data, UserData}];
198parse_sccp_msgt(?SCCP_MSGT_AK, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100199 <<_:8, DstLocalRef:24/big, RxSeqnr:8, Credit:8>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100200 [{dst_local_ref, DstLocalRef},{rx_seq_nr, RxSeqnr},{credit, Credit}];
201parse_sccp_msgt(?SCCP_MSGT_UDT, DataBin) ->
Harald Welte11565772011-04-15 10:37:57 +0200202 <<_:8, PCOpt:4, ProtoClass:4, CalledPartyPtr:8, CallingPartyPtr:8, DataPtr:8, Remain/binary >> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100203 % variable part
204 CalledPartyLen = binary:at(Remain, CalledPartyPtr-3),
205 CalledParty = binary:part(Remain, CalledPartyPtr-3+1, CalledPartyLen),
Harald Welte234c9562011-02-03 13:51:12 +0100206 CalledPartyDec = parse_sccp_addr(CalledParty),
Harald Welte033cef02010-12-19 22:47:14 +0100207 CallingPartyLen = binary:at(Remain, CallingPartyPtr-2),
208 CallingParty = binary:part(Remain, CallingPartyPtr-2+1, CallingPartyLen),
Harald Welte234c9562011-02-03 13:51:12 +0100209 CallingPartyDec = parse_sccp_addr(CallingParty),
Harald Welte033cef02010-12-19 22:47:14 +0100210 DataLen = binary:at(Remain, DataPtr-1),
211 UserData = binary:part(Remain, DataPtr-1+1, DataLen),
Harald Welte11565772011-04-15 10:37:57 +0200212 [{protocol_class, {ProtoClass, PCOpt}},{called_party_addr, CalledPartyDec},
Harald Welte234c9562011-02-03 13:51:12 +0100213 {calling_party_addr, CallingPartyDec},{user_data, UserData}];
Harald Welte033cef02010-12-19 22:47:14 +0100214parse_sccp_msgt(?SCCP_MSGT_UDTS, DataBin) ->
Harald Welte030f1092011-03-11 19:08:07 +0100215 <<_:8, ReturnCause:8, CalledPartyPtr:8, CallingPartyPtr:8, DataPtr:8, Remain/binary >> = DataBin,
216 % variable part
217 CalledPartyLen = binary:at(Remain, CalledPartyPtr-3),
218 CalledParty = binary:part(Remain, CalledPartyPtr-3+1, CalledPartyLen),
219 CalledPartyDec = parse_sccp_addr(CalledParty),
220 CallingPartyLen = binary:at(Remain, CallingPartyPtr-2),
221 CallingParty = binary:part(Remain, CallingPartyPtr-2+1, CallingPartyLen),
222 CallingPartyDec = parse_sccp_addr(CallingParty),
223 DataLen = binary:at(Remain, DataPtr-1),
224 UserData = binary:part(Remain, DataPtr-1+1, DataLen),
225 [{return_cause, ReturnCause},{called_party_addr, CalledPartyDec},
226 {calling_party_addr, CallingPartyDec},{user_data, UserData}];
Harald Welte033cef02010-12-19 22:47:14 +0100227parse_sccp_msgt(?SCCP_MSGT_ED, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100228 <<_:8, DstLocalRef:24/big, DataPtr:8, Remain/binary>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100229 DataLen = binary:at(Remain, DataPtr-1),
230 UserData = binary:part(Remain, DataPtr-1+1, DataLen),
231 [{dst_local_ref, DstLocalRef}, {user_data, UserData}];
232parse_sccp_msgt(?SCCP_MSGT_EA, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100233 <<_:8, DstLocalRef:24/big>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100234 [{dst_local_ref, DstLocalRef}];
235parse_sccp_msgt(?SCCP_MSGT_RSR, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100236 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big, ResetCause:8>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100237 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},{reset_cause, ResetCause}];
238parse_sccp_msgt(?SCCP_MSGT_RSC, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100239 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100240 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef}];
241parse_sccp_msgt(?SCCP_MSGT_ERR, DataBin) ->
Harald Welte56ee7a62010-12-20 13:34:32 +0100242 <<_:8, DstLocalRef:24/big, ErrCause:8>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100243 [{dst_local_ref, DstLocalRef},{error_cause, ErrCause}];
244parse_sccp_msgt(?SCCP_MSGT_IT, DataBin) ->
Harald Welte11565772011-04-15 10:37:57 +0200245 <<_:8, DstLocalRef:24/big, SrcLocalRef:24/big, PCOpt: 4, ProtoClass:4, SegmSeq:16, Credit:8>> = DataBin,
Harald Welte033cef02010-12-19 22:47:14 +0100246 [{dst_local_ref, DstLocalRef},{src_local_ref, SrcLocalRef},
Harald Welte11565772011-04-15 10:37:57 +0200247 {protocol_class, {ProtoClass, PCOpt}},{seq_segm, SegmSeq},{credit, Credit}].
Harald Welte033cef02010-12-19 22:47:14 +0100248% FIXME: XUDT/XUDTS, LUDT/LUDTS
249
250% process one incoming SCCP message
251parse_sccp_msg(DataBin) ->
252 MsgType = binary:first(DataBin),
253 Parsed = parse_sccp_msgt(MsgType, DataBin),
254 {ok, #sccp_msg{msg_type = MsgType, parameters = Parsed}}.
255
256% Encoding Part
257
Harald Welte0e1709c2011-02-06 22:17:53 +0100258gt_enc_by_odd(Odd) ->
259 if Odd == 1 ->
260 1;
261 true ->
262 2
263 end.
264
Harald Welte5a1cf3c2011-04-14 21:55:13 +0200265encode_gt(undefined) ->
266 {?SCCP_GTI_NO_GT, <<>>};
Harald Welte234c9562011-02-03 13:51:12 +0100267encode_gt(#global_title{gti = GTind, phone_number = PhoneNum,
268 nature_of_addr_ind = Nature,
Harald Welte2c67ac02012-01-18 08:49:45 +0100269 trans_type = TransType,
Harald Welte234c9562011-02-03 13:51:12 +0100270 numbering_plan = NumPlan}) ->
271 case GTind of
272 ?SCCP_GTI_NO_GT ->
273 {GTind, <<>>};
274 ?SCCP_GTI_NAT_ONLY ->
275 % Figure 7/Q.713
276 {PhoneBin, OddEven} = isup_codec:encode_isup_party(PhoneNum),
277 {GTind, <<OddEven:1, Nature:7, PhoneBin/binary>>};
278 ?SCCP_GTI_TT_ONLY ->
279 % Figure 9/Q.913
280 % Used in national interfaces only, we cannot parse Digits
281 {GTind, <<TransType:8, PhoneNum/binary>>};
282 ?SCCP_GTI_TT_NP_ENC ->
283 % Figure 10/Q.713
Harald Welte0e1709c2011-02-06 22:17:53 +0100284 {PhoneBin, OddEven} = isup_codec:encode_isup_party(PhoneNum),
285 Enc = gt_enc_by_odd(OddEven),
Harald Welte234c9562011-02-03 13:51:12 +0100286 {GTind, <<TransType:8, NumPlan:4, Enc:4, PhoneBin/binary>>};
287 ?SCCP_GTI_TT_NP_ENC_NAT ->
288 % Figure 11/Q.713
Harald Welte0e1709c2011-02-06 22:17:53 +0100289 {PhoneBin, OddEven} = isup_codec:encode_isup_party(PhoneNum),
290 Enc = gt_enc_by_odd(OddEven),
Harald Welte234c9562011-02-03 13:51:12 +0100291 {GTind, <<TransType:8, NumPlan:4, Enc:4, 0:1, Nature:7, PhoneBin/binary>>}
292 end.
293
Harald Weltec923a2a2012-01-23 14:13:05 +0100294encode_pc(undefined) ->
295 {0, <<>>};
Harald Welte683ed232011-12-08 00:56:54 +0100296encode_pc(PointCode) when is_integer(PointCode) ->
Harald Weltec923a2a2012-01-23 14:13:05 +0100297 {1, <<PointCode:16/little>>};
Harald Welte683ed232011-12-08 00:56:54 +0100298encode_pc(PcRec) ->
299 PcInt = osmo_util:pointcode2int(PcRec),
300 encode_pc(PcInt).
Harald Welte234c9562011-02-03 13:51:12 +0100301
302encode_ssn(SSN) ->
303 case SSN of
Harald Welteb5936ba2011-12-08 00:58:51 +0100304 undefined ->
Harald Welte234c9562011-02-03 13:51:12 +0100305 {0, <<>>};
306 _ ->
307 {1, <<SSN:8>>}
308 end.
309
Harald Welte5a1cf3c2011-04-14 21:55:13 +0200310undef_or_true(Foo) ->
311 case Foo of
312 undefined -> 0;
313 0 -> 0;
314 _ -> 1
315 end.
316
317
Harald Welte234c9562011-02-03 13:51:12 +0100318encode_sccp_addr(#sccp_addr{res_nat_use = ResNatUse,
319 route_on_ssn = RoutInd,
320 point_code = PointCode,
321 ssn = SSN,
322 global_title = GT}) ->
323
324 {GTind, GTbin} = encode_gt(GT),
325 {SSNind, SSNbin} = encode_ssn(SSN),
326 {PCind, PCbin} = encode_pc(PointCode),
Harald Welte5a1cf3c2011-04-14 21:55:13 +0200327 ResNatOut = undef_or_true(ResNatUse),
328 RoutIndOut = undef_or_true(RoutInd),
329 <<ResNatOut:1, RoutIndOut:1, GTind:4, SSNind:1, PCind:1, PCbin/binary, SSNbin/binary, GTbin/binary>>.
Harald Welte234c9562011-02-03 13:51:12 +0100330
331
Harald Welte9dda4e12012-01-23 16:15:06 +0100332encode_sccp_opt({AddrTag, AddrVal}) when AddrTag == ?SCCP_PNC_CALLED_PARTY_ADDRESS;
333 AddrTag == ?SCCP_PNC_CALLING_PARTY_ADDRESS ->
334 AddrEnc = encode_sccp_addr(AddrVal),
335 AddrLen = byte_size(AddrEnc),
336 <<AddrTag:8, AddrLen:8, AddrEnc/binary>>;
337encode_sccp_opt({OptInt, DataBin}) when is_binary(DataBin), is_integer(OptInt) ->
338 DataBinLen = byte_size(DataBin),
339 <<OptInt:8, DataBinLen:8, DataBin/binary>>;
340encode_sccp_opt({Opt, DataBin}) when is_atom(Opt) ->
341 OptNum = atom_to_opt(Opt),
342 encode_sccp_opt({OptNum, DataBin});
343encode_sccp_opt({Opt, DataInt}) when is_integer(DataInt), DataInt =< 255 ->
344 encode_sccp_opt({Opt, <<DataInt:8>>});
345encode_sccp_opt({Opt, DataList}) when is_list(DataList) ->
346 encode_sccp_opt({Opt, list_to_binary(DataList)}).
Harald Welte033cef02010-12-19 22:47:14 +0100347
Harald Welte9dda4e12012-01-23 16:15:06 +0100348encode_sccp_opts(OptList, Filter) ->
349 FilteredList = lists:filter(fun({Tag, _Val}) -> proplists:is_defined(opt_to_atom(Tag), Filter) end, OptList),
350 e_sccp_opts(FilteredList, []).
351
352e_sccp_opts([], OptEnc) ->
Harald Welte033cef02010-12-19 22:47:14 +0100353 % end of options + convert to binary
354 list_to_binary([OptEnc, ?SCCP_PNC_END_OF_OPTIONAL]);
Harald Welte9dda4e12012-01-23 16:15:06 +0100355e_sccp_opts([CurOpt|OptPropList], OptEnc) ->
Harald Welte033cef02010-12-19 22:47:14 +0100356 CurOptEnc = encode_sccp_opt(CurOpt),
Harald Welte9dda4e12012-01-23 16:15:06 +0100357 e_sccp_opts(OptPropList, list_to_binary([OptEnc,CurOptEnc])).
Harald Welte033cef02010-12-19 22:47:14 +0100358
Harald Welte033cef02010-12-19 22:47:14 +0100359
360encode_sccp_msgt(?SCCP_MSGT_CR, Params) ->
361 SrcLocalRef = proplists:get_value(src_local_ref, Params),
Harald Welte11565772011-04-15 10:37:57 +0200362 {ProtoClass, PCOpt} = proplists:get_value(protocol_class, Params),
Harald Welte9dda4e12012-01-23 16:15:06 +0100363 CalledParty = proplists:get_value(called_party_addr, Params),
364 CalledPartyEnc = encode_sccp_addr(CalledParty),
365 CalledPartyLen = byte_size(CalledPartyEnc),
366 PtrOpt = CalledPartyLen+1+1,
367 OptBin = encode_sccp_opts(Params, [credit, calling_party_addr, user_data, hop_counter, importance]),
368 <<?SCCP_MSGT_CR:8, SrcLocalRef:24/big, PCOpt:4, ProtoClass:4, 2:8, PtrOpt:8, CalledPartyLen:8, CalledPartyEnc/binary, OptBin/binary>>;
Harald Welte033cef02010-12-19 22:47:14 +0100369encode_sccp_msgt(?SCCP_MSGT_CC, Params) ->
370 SrcLocalRef = proplists:get_value(src_local_ref, Params),
371 DstLocalRef = proplists:get_value(dst_local_ref, Params),
Harald Welte11565772011-04-15 10:37:57 +0200372 {ProtoClass, PCOpt} = proplists:get_value(protocol_class, Params),
Harald Welte9dda4e12012-01-23 16:15:06 +0100373 OptBin = encode_sccp_opts(Params, [credit, called_party_addr, user_data, importance]),
Harald Welte11565772011-04-15 10:37:57 +0200374 <<?SCCP_MSGT_CC:8, DstLocalRef:24/big, SrcLocalRef:24/big, PCOpt:4, ProtoClass:4, OptBin/binary>>;
Harald Welte033cef02010-12-19 22:47:14 +0100375encode_sccp_msgt(?SCCP_MSGT_CREF, Params) ->
376 DstLocalRef = proplists:get_value(dst_local_ref, Params),
377 RefusalCause = proplists:get_value(refusal_cause, Params),
Harald Welte9dda4e12012-01-23 16:15:06 +0100378 OptBin = encode_sccp_opts(Params, [called_party_addr, user_data, importance]),
Harald Welte56ee7a62010-12-20 13:34:32 +0100379 <<?SCCP_MSGT_CREF:8, DstLocalRef:24/big, RefusalCause:8, OptBin/binary>>;
Harald Welte033cef02010-12-19 22:47:14 +0100380encode_sccp_msgt(?SCCP_MSGT_RLSD, Params) ->
381 SrcLocalRef = proplists:get_value(src_local_ref, Params),
382 DstLocalRef = proplists:get_value(dst_local_ref, Params),
383 ReleaseCause = proplists:get_value(release_cause, Params),
Harald Welte9dda4e12012-01-23 16:15:06 +0100384 OptBin = encode_sccp_opts(Params, [user_data, importance]),
Harald Welte56ee7a62010-12-20 13:34:32 +0100385 <<?SCCP_MSGT_RLSD:8, DstLocalRef:24/big, SrcLocalRef:24/big, ReleaseCause:8, OptBin/binary>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100386encode_sccp_msgt(?SCCP_MSGT_RLC, Params) ->
387 SrcLocalRef = proplists:get_value(src_local_ref, Params),
388 DstLocalRef = proplists:get_value(dst_local_ref, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100389 <<?SCCP_MSGT_RLC:8, DstLocalRef:24/big, SrcLocalRef:24/big>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100390encode_sccp_msgt(?SCCP_MSGT_DT1, Params) ->
391 DstLocalRef = proplists:get_value(dst_local_ref, Params),
392 SegmReass = proplists:get_value(segm_reass, Params),
Harald Welted9c318f2011-12-10 22:17:11 +0100393 UserData = binarify(proplists:get_value(user_data, Params)),
Harald Weltec0696b02010-12-20 00:09:37 +0100394 UserDataLen = byte_size(UserData),
Harald Welte56ee7a62010-12-20 13:34:32 +0100395 <<?SCCP_MSGT_DT1:8, DstLocalRef:24/big, SegmReass:8, 1:8, UserDataLen:8, UserData/binary>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100396encode_sccp_msgt(?SCCP_MSGT_DT2, Params) ->
397 DstLocalRef = proplists:get_value(dst_local_ref, Params),
398 SeqSegm = proplists:get_value(seq_segm, Params),
Harald Welted9c318f2011-12-10 22:17:11 +0100399 UserData = binarify(proplists:get_value(user_data, Params)),
Harald Weltec0696b02010-12-20 00:09:37 +0100400 UserDataLen = byte_size(UserData),
Harald Welte56ee7a62010-12-20 13:34:32 +0100401 <<?SCCP_MSGT_DT2:8, DstLocalRef:24/big, SeqSegm:16, 1:8, UserDataLen:8, UserData/binary>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100402encode_sccp_msgt(?SCCP_MSGT_AK, Params) ->
403 DstLocalRef = proplists:get_value(dst_local_ref, Params),
404 RxSeqnr = proplists:get_value(rx_seqnr, Params),
405 Credit = proplists:get_value(credit, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100406 <<?SCCP_MSGT_AK:8, DstLocalRef:24/big, RxSeqnr:8, Credit:8>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100407encode_sccp_msgt(?SCCP_MSGT_UDT, Params) ->
Harald Welte11565772011-04-15 10:37:57 +0200408 {ProtoClass, PCOpt} = proplists:get_value(protocol_class, Params),
Harald Weltec0696b02010-12-20 00:09:37 +0100409 CalledParty = proplists:get_value(called_party_addr, Params),
Harald Welte234c9562011-02-03 13:51:12 +0100410 CalledPartyEnc = encode_sccp_addr(CalledParty),
411 CalledPartyLen = byte_size(CalledPartyEnc),
Harald Weltec0696b02010-12-20 00:09:37 +0100412 CallingParty = proplists:get_value(calling_party_addr, Params),
Harald Welte234c9562011-02-03 13:51:12 +0100413 CallingPartyEnc = encode_sccp_addr(CallingParty),
414 CallingPartyLen = byte_size(CallingPartyEnc),
Harald Welted9c318f2011-12-10 22:17:11 +0100415 UserData = binarify(proplists:get_value(user_data, Params)),
Harald Weltec0696b02010-12-20 00:09:37 +0100416 UserDataLen = byte_size(UserData),
417 % variable part
418 CalledPartyPtr = 3,
419 CallingPartyPtr = 2 + (1 + CalledPartyLen),
420 DataPtr = 1 + (1 + CalledPartyLen) + (1 + CallingPartyLen),
Harald Welte234c9562011-02-03 13:51:12 +0100421 Remain = <<CalledPartyLen:8, CalledPartyEnc/binary,
422 CallingPartyLen:8, CallingPartyEnc/binary,
Harald Weltec0696b02010-12-20 00:09:37 +0100423 UserDataLen:8, UserData/binary>>,
Harald Welte11565772011-04-15 10:37:57 +0200424 <<?SCCP_MSGT_UDT:8, PCOpt:4, ProtoClass:4, CalledPartyPtr:8, CallingPartyPtr:8, DataPtr:8, Remain/binary>>;
Harald Welte030f1092011-03-11 19:08:07 +0100425encode_sccp_msgt(?SCCP_MSGT_UDTS, Params) ->
426 ReturnCause = proplists:get_value(return_cause, Params),
427 CalledParty = proplists:get_value(called_party_addr, Params),
428 CalledPartyEnc = encode_sccp_addr(CalledParty),
429 CalledPartyLen = byte_size(CalledPartyEnc),
430 CallingParty = proplists:get_value(calling_party_addr, Params),
431 CallingPartyEnc = encode_sccp_addr(CallingParty),
432 CallingPartyLen = byte_size(CallingPartyEnc),
Harald Welted9c318f2011-12-10 22:17:11 +0100433 UserData = binarify(proplists:get_value(user_data, Params)),
Harald Welte030f1092011-03-11 19:08:07 +0100434 UserDataLen = byte_size(UserData),
435 % variable part
436 CalledPartyPtr = 3,
437 CallingPartyPtr = 2 + (1 + CalledPartyLen),
438 DataPtr = 1 + (1 + CalledPartyLen) + (1 + CallingPartyLen),
439 Remain = <<CalledPartyLen:8, CalledPartyEnc/binary,
440 CallingPartyLen:8, CallingPartyEnc/binary,
441 UserDataLen:8, UserData/binary>>,
442 <<?SCCP_MSGT_UDTS:8, ReturnCause:8, CalledPartyPtr:8, CallingPartyPtr:8, DataPtr:8, Remain/binary>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100443encode_sccp_msgt(?SCCP_MSGT_ED, Params) ->
444 DstLocalRef = proplists:get_value(dst_local_ref, Params),
Harald Welted9c318f2011-12-10 22:17:11 +0100445 UserData = binarify(proplists:get_value(user_data, Params)),
Harald Weltec0696b02010-12-20 00:09:37 +0100446 UserDataLen = byte_size(UserData),
447 DataPtr = 1,
Harald Welte56ee7a62010-12-20 13:34:32 +0100448 <<?SCCP_MSGT_ED:8, DstLocalRef:24/big, DataPtr:8, UserDataLen:8, UserData/binary>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100449encode_sccp_msgt(?SCCP_MSGT_EA, Params) ->
450 DstLocalRef = proplists:get_value(dst_local_ref, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100451 <<?SCCP_MSGT_EA:8, DstLocalRef:24/big>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100452encode_sccp_msgt(?SCCP_MSGT_RSR, Params) ->
453 DstLocalRef = proplists:get_value(dst_local_ref, Params),
454 SrcLocalRef = proplists:get_value(src_local_ref, Params),
455 ResetCause = proplists:get_value(reset_cause, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100456 <<?SCCP_MSGT_RSR:8, DstLocalRef:24/big, SrcLocalRef:24/big, ResetCause:8>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100457encode_sccp_msgt(?SCCP_MSGT_RSC, Params) ->
458 DstLocalRef = proplists:get_value(dst_local_ref, Params),
459 SrcLocalRef = proplists:get_value(src_local_ref, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100460 <<?SCCP_MSGT_RSC:8, DstLocalRef:24/big, SrcLocalRef:24/big>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100461encode_sccp_msgt(?SCCP_MSGT_ERR, Params) ->
462 DstLocalRef = proplists:get_value(dst_local_ref, Params),
463 ErrCause = proplists:get_value(error_cause, Params),
Harald Welte56ee7a62010-12-20 13:34:32 +0100464 <<?SCCP_MSGT_ERR:8, DstLocalRef:24/big, ErrCause:8>>;
Harald Weltec0696b02010-12-20 00:09:37 +0100465encode_sccp_msgt(?SCCP_MSGT_IT, Params) ->
466 DstLocalRef = proplists:get_value(dst_local_ref, Params),
467 SrcLocalRef = proplists:get_value(src_local_ref, Params),
Harald Welte11565772011-04-15 10:37:57 +0200468 {ProtoClass, PCOpt} = proplists:get_value(protocol_class, Params),
Harald Welte09b43992010-12-20 12:21:03 +0100469 SegmSeq = proplists:get_value(seq_segm, Params),
Harald Weltec0696b02010-12-20 00:09:37 +0100470 Credit = proplists:get_value(credit, Params),
Harald Welte11565772011-04-15 10:37:57 +0200471 <<?SCCP_MSGT_IT:8, DstLocalRef:24/big, SrcLocalRef:24/big, PCOpt:4, ProtoClass:4, SegmSeq:16, Credit:8>>.
Harald Weltec0696b02010-12-20 00:09:37 +0100472% FIXME: XUDT/XUDTS, LUDT/LUDTS
473
Harald Welte033cef02010-12-19 22:47:14 +0100474
475% encode one sccp message data structure into the on-wire format
476encode_sccp_msg(#sccp_msg{msg_type = MsgType, parameters = Params}) ->
477 encode_sccp_msgt(MsgType, Params).
Harald Welte9abbbad2011-04-21 12:19:41 +0200478
479% is the supplied message type a connectionless message?
480is_connectionless(#sccp_msg{msg_type = MsgType}) ->
481 is_connectionless(MsgType);
482is_connectionless(MsgType) ->
483 case MsgType of
484 ?SCCP_MSGT_UDT -> true;
485 ?SCCP_MSGT_UDTS -> true;
486 ?SCCP_MSGT_XUDT -> true;
487 ?SCCP_MSGT_XUDTS -> true;
488 ?SCCP_MSGT_LUDT -> true;
489 ?SCCP_MSGT_LUDTS -> true;
490 _ -> false
491 end.
Harald Welte9baab6d2011-12-08 00:46:00 +0100492
493
494gen_gt_helper(Number) when is_list(Number) ->
495 #global_title{gti=?SCCP_GTI_NAT_ONLY,
496 nature_of_addr_ind=?SCCP_NAI_INTERNATIONAL,
497 phone_number = Number}.
498
499gen_addr_helper(Gt, Pc, Ssn) when is_record(Gt, global_title) ->
500 #sccp_addr{point_code=Pc, ssn=Ssn, global_title=Gt};
501gen_addr_helper(Number, Pc, Ssn) when is_list(Number) ->
502 Gt = gen_gt_helper(Number),
503 gen_addr_helper(Gt, Pc, Ssn).
504
505
506gen_addr_helper(Gt, Pc) when is_record(Gt, global_title) ->
507 #sccp_addr{point_code=Pc, global_title=Gt};
508gen_addr_helper(Number, Pc) when is_list(Number) ->
509 Gt = gen_gt_helper(Number),
510 gen_addr_helper(Gt, Pc).
Harald Welte9dda4e12012-01-23 16:15:06 +0100511
512opt_to_atom(Num) ->
513 case Num of
514 ?SCCP_PNC_DESTINATION_LOCAL_REFERENCE -> dst_local_ref;
515 ?SCCP_PNC_SOURCE_LOCAL_REFERENCE -> src_local_ref;
516 ?SCCP_PNC_CALLED_PARTY_ADDRESS -> called_party_addr;
517 ?SCCP_PNC_CALLING_PARTY_ADDRESS -> calling_party_addr;
518 ?SCCP_PNC_PROTOCOL_CLASS -> protocol_class;
519 ?SCCP_PNC_SEGMENTING -> segmenting;
520 ?SCCP_PNC_RECEIVE_SEQ_NUMBER -> rx_seq_number;
521 ?SCCP_PNC_SEQUENCING -> seq_segm;
522 ?SCCP_PNC_CREDIT -> credit;
523 ?SCCP_PNC_RELEASE_CAUSE -> release_cause;
524 ?SCCP_PNC_RETURN_CAUSE -> return_cause;
525 ?SCCP_PNC_RESET_CAUSE -> reset_cause;
526 ?SCCP_PNC_ERROR_CAUSE -> error_cause;
527 ?SCCP_PNC_REFUSAL_CAUSE -> refusal_cause;
528 ?SCCP_PNC_DATA -> user_data;
529 ?SCCP_PNC_SEGMENTATION -> segmentation;
530 ?SCCP_PNC_HOP_COUNTER -> hop_counter;
531 ?SCCP_PNC_IMPORTANCE -> importance;
532 ?SCCP_PNC_LONG_DATA -> long_data;
533 Foo -> Foo
534 end.
535
536atom_to_opt(Atom) ->
537 case Atom of
538 dst_local_ref -> ?SCCP_PNC_DESTINATION_LOCAL_REFERENCE;
539 src_local_ref -> ?SCCP_PNC_SOURCE_LOCAL_REFERENCE;
540 called_party_addr -> ?SCCP_PNC_CALLED_PARTY_ADDRESS;
541 calling_party_addr -> ?SCCP_PNC_CALLING_PARTY_ADDRESS;
542 protocol_class -> ?SCCP_PNC_PROTOCOL_CLASS;
543 segmenting -> ?SCCP_PNC_SEGMENTING;
544 rx_seq_number -> ?SCCP_PNC_RECEIVE_SEQ_NUMBER;
545 seq_segm -> ?SCCP_PNC_SEQUENCING;
546 credit -> ?SCCP_PNC_CREDIT;
547 release_cause -> ?SCCP_PNC_RELEASE_CAUSE;
548 return_cause -> ?SCCP_PNC_RETURN_CAUSE;
549 reset_cause -> ?SCCP_PNC_RESET_CAUSE;
550 error_cause -> ?SCCP_PNC_ERROR_CAUSE;
551 refusal_cause -> ?SCCP_PNC_REFUSAL_CAUSE;
552 user_data -> ?SCCP_PNC_DATA;
553 segmentation -> ?SCCP_PNC_SEGMENTATION;
554 hop_counter -> ?SCCP_PNC_HOP_COUNTER;
555 importance -> ?SCCP_PNC_IMPORTANCE;
556 long_data -> ?SCCP_PNC_LONG_DATA;
557 Foo -> Foo
558 end.