blob: e3f4c6c6bfb1bea76fc3ec681913be05a6ae2320 [file] [log] [blame]
Harald Welte50dfc192012-01-17 15:11:37 +01001% Conversion between SUA messages and #sccp_msg{}
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 Welte50dfc192012-01-17 15:11:37 +010033
34% FIXME: this currently only supports connection-less SCCP
35
36-module(sua_sccp_conv).
37-author('Harald Welte <laforge@gnumonks.org>').
38
39-include("sua.hrl").
Harald Welte92e783d2012-04-01 19:52:01 +020040-include("xua.hrl").
Harald Welte50dfc192012-01-17 15:11:37 +010041-include("sccp.hrl").
42
43-export([sua_to_sccp/1, sccp_to_sua/1]).
44
Harald Welte92e783d2012-04-01 19:52:01 +020045sua_to_sccp(M=#xua_msg{msg_class = Class, msg_type = Type}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010046 sua_to_sccp(Class, Type, M).
47sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDT, Sua) ->
48 Params = sua_to_sccp_params(Sua),
49 #sccp_msg{msg_type = ?SCCP_MSGT_UDT,
50 parameters = Params};
51sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDR, Sua) ->
52 Params = sua_to_sccp_params(Sua),
53 #sccp_msg{msg_type = ?SCCP_MSGT_UDTS,
54 parameters = Params}.
55
Harald Welte99efaf92012-01-18 14:11:23 +010056sccp_to_sua(#sccp_msg{msg_type = Type, parameters = Params}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010057 sccp_to_sua(Type, Params).
58sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDT;
59 Type == ?SCCP_MSGT_XUDT;
60 Type == ?SCCP_MSGT_LUDT ->
Harald Welte8e92c9a2012-01-18 00:25:26 +010061 Opts = sccp_to_sua_params(Type, Params),
Harald Welte92e783d2012-04-01 19:52:01 +020062 #xua_msg{version = 1, msg_class = ?SUA_MSGC_CL,
Harald Welte8e92c9a2012-01-18 00:25:26 +010063 msg_type = ?SUA_CL_CLDT, payload = Opts};
Harald Welte50dfc192012-01-17 15:11:37 +010064sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDTS;
65 Type == ?SCCP_MSGT_XUDTS;
66 Type == ?SCCP_MSGT_LUDTS ->
67 Opts = sccp_to_sua_params(Params),
Harald Welte92e783d2012-04-01 19:52:01 +020068 #xua_msg{version=1, msg_class = ?SUA_MSGC_CL,
Harald Welte8e92c9a2012-01-18 00:25:26 +010069 msg_type = ?SUA_CL_CLDR, payload = Opts}.
Harald Welte50dfc192012-01-17 15:11:37 +010070
71
72% CLDT parameters:
73% ?SUA_IEI_ROUTE_CTX, ?SUA_IEI_PROTO_CLASS, ?SUA_IEI_SRC_ADDR,
74% ?SUA_IEI_DEST_ADDR, ?SUA_IEI_SEQ_CTRL, ?SUA_IEI_S7_HOP_CTR,
75% ?SUA_IEI_IMPORTANCE, ?SUA_IEI_MSG_PRIO, ?SUA_IEI_CORR_ID,
76% ?SUA_IEI_SEGMENTATION, ?SUA_IEI_DATA
77
Harald Welte92e783d2012-04-01 19:52:01 +020078sua_to_sccp_params(#xua_msg{msg_class=Class, msg_type=Type, payload=Payload}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010079 sua_to_sccp_params(Class, Type, Payload).
80sua_to_sccp_params(Class, Type, Payload) ->
81 sua_to_sccp_params(Class, Type, Payload, []).
Harald Welte99efaf92012-01-18 14:11:23 +010082sua_to_sccp_params(_Class, _Type, [], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +010083 List;
Harald Welte042a5792012-01-18 00:09:51 +010084sua_to_sccp_params(Class, Type, [{ParTag, {_Len, ParVal}}|Remain], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +010085 NewPars = sua_to_sccp_param(Class, Type, ParTag, ParVal),
86 sua_to_sccp_params(Class, Type, Remain, List ++ NewPars).
87
88% convert an individual SUA parameter to a SCCP option
89sua_to_sccp_param(_, _, ?SUA_IEI_PROTO_CLASS, Remain) ->
Harald Welte99efaf92012-01-18 14:11:23 +010090 <<_:24, PCOpt:4, _:2, Class:2>> = Remain,
91 [{protocol_class, {Class, PCOpt}}];
Harald Welte50dfc192012-01-17 15:11:37 +010092sua_to_sccp_param(_, _, ?SUA_IEI_SRC_ADDR, Remain) ->
93 Addr = sua_to_sccp_addr(Remain),
Harald Welte7e1c2612012-01-18 07:44:31 +010094 [{calling_party_addr, Addr}];
Harald Welte50dfc192012-01-17 15:11:37 +010095sua_to_sccp_param(_, _, ?SUA_IEI_DEST_ADDR, Remain) ->
96 Addr = sua_to_sccp_addr(Remain),
Harald Welte7e1c2612012-01-18 07:44:31 +010097 [{called_party_addr, Addr}];
Harald Welte99efaf92012-01-18 14:11:23 +010098sua_to_sccp_param(_, _, ?SUA_IEI_SEQ_CTRL, _Remain) ->
99 % If we were to translate to a N-UNITDATA.req, we could map
100 % this, but there is no mapping to a SCCP message...
101 [];
Harald Welte50dfc192012-01-17 15:11:37 +0100102sua_to_sccp_param(_, _, ?SUA_IEI_S7_HOP_CTR, Remain) ->
103 <<_:24, HopCtr:8>> = Remain,
104 [{?SCCP_PNC_HOP_COUNTER, HopCtr}];
105sua_to_sccp_param(_, _, ?SUA_IEI_IMPORTANCE, Remain) ->
106 <<_:24, Imp:8>> = Remain,
107 [{?SCCP_PNC_IMPORTANCE, Imp}];
108sua_to_sccp_param(_, _, ?SUA_IEI_DATA, Remain) ->
Harald Welte7e1c2612012-01-18 07:44:31 +0100109 [{user_data, Remain}];
Harald Welte99efaf92012-01-18 14:11:23 +0100110sua_to_sccp_param(_, _, ?SUA_IEI_ROUTE_CTX, _Remain) ->
Harald Welte042a5792012-01-18 00:09:51 +0100111 %FIXME: what to do with routing context?
112 [].
Harald Welte50dfc192012-01-17 15:11:37 +0100113
114sccp_to_sua_params(#sccp_msg{msg_type=Type, parameters=Params}) ->
115 sccp_to_sua_params(Type, Params).
116sccp_to_sua_params(Type, Params) when is_list(Params) ->
117 sccp_to_sua_params(Type, Params, []).
Harald Welte99efaf92012-01-18 14:11:23 +0100118sccp_to_sua_params(_Type, [], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100119 List;
120sccp_to_sua_params(Type, [{ParTag, ParVal}|Tail], List) ->
121 NewPars = sccp_to_sua_param(Type, ParTag, ParVal),
122 sccp_to_sua_params(Type, Tail, List ++ NewPars).
123
Harald Welte99efaf92012-01-18 14:11:23 +0100124sccp_to_sua_param(_, protocol_class, {Opt, Class}) ->
125 [{?SUA_IEI_PROTO_CLASS, <<0:24, Opt:4, 0:2, Class:2>>}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100126sccp_to_sua_param(_, calling_party_addr, Addr) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100127 AddrSua = sccp_to_sua_addr(Addr),
128 [{?SUA_IEI_SRC_ADDR, AddrSua}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100129sccp_to_sua_param(_, called_party_addr, Addr) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100130 AddrSua = sccp_to_sua_addr(Addr),
131 [{?SUA_IEI_DEST_ADDR, AddrSua}];
Harald Welte50dfc192012-01-17 15:11:37 +0100132sccp_to_sua_param(_, ?SCCP_PNC_HOP_COUNTER, Hop) ->
133 [{?SUA_IEI_S7_HOP_CTR, <<0:24, Hop:8>>}];
134sccp_to_sua_param(_, ?SCCP_PNC_IMPORTANCE, Imp) ->
135 [{?SUA_IEI_IMPORTANCE, <<0:24, Imp:8>>}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100136sccp_to_sua_param(_, user_data, Data) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100137 [{?SUA_IEI_DATA, Data}].
138
139sua_to_sccp_addr(SuaBin) ->
140 <<RoutInd:16, _:13, GTinc:1, PCinc:1, SSNinc:1, Remain/binary>> = SuaBin,
141 ParList = addr_pars_to_list(Remain),
142 case GTinc of
143 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100144 {_, GTopt} = proplists:get_value(?SUA_IEI_GT, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100145 GT = parse_sua_gt(GTopt);
146 0 ->
147 GT = undefined
148 end,
149 case PCinc of
150 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100151 {_, PCopt} = proplists:get_value(?SUA_IEI_PC, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100152 PC = parse_sua_pc(PCopt);
153 0 ->
154 PC = undefined
155 end,
156 case SSNinc of
157 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100158 {_, SSNopt} = proplists:get_value(?SUA_IEI_SSN, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100159 SSN = parse_sua_ssn(SSNopt);
160 0 ->
161 SSN = undefined
162 end,
163 case RoutInd of
164 ?SUA_RI_GT ->
165 RoutSSN = 0;
166 ?SUA_RI_SSN_PC ->
167 RoutSSN = 1
168 end,
169 #sccp_addr{route_on_ssn = RoutSSN, point_code = PC, ssn = SSN, global_title = GT}.
170
171addr_pars_to_list(Bin) ->
Harald Welte92e783d2012-04-01 19:52:01 +0200172 xua_codec:parse_xua_opts(Bin).
Harald Welte50dfc192012-01-17 15:11:37 +0100173
174sccp_to_sua_addr(Addr) when is_record(Addr, sccp_addr) ->
175 #sccp_addr{route_on_ssn = RoutOnSsn, point_code = PC, ssn = SSN,
176 global_title = GT} = Addr,
177 case GT of
178 #global_title{} ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100179 GTopt = [{?SUA_IEI_GT, encode_sua_gt(GT)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100180 GTinc = 1;
181 _ ->
182 GTopt = [],
183 GTinc = 0
184 end,
185 case PC of
186 Int when is_integer(Int) ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100187 PCopt = [{?SUA_IEI_PC, encode_sua_pc(PC)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100188 PCinc = 1;
189 _ ->
190 PCopt = [],
191 PCinc = 0
192 end,
193 case SSN of
194 Int2 when is_integer(Int2) ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100195 SSNopt = [{?SUA_IEI_SSN, encode_sua_ssn(SSN)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100196 SSNinc = 1;
197 _ ->
198 SSNopt = [],
199 SSNinc = 0
200 end,
201 case RoutOnSsn of
202 0 ->
203 RoutInd = ?SUA_RI_GT;
204 1 ->
205 RoutInd = ?SUA_RI_SSN_PC
206 end,
Harald Welte92e783d2012-04-01 19:52:01 +0200207 Tail = xua_codec:encode_xua_opts(GTopt ++ PCopt ++ SSNopt),
Harald Welte50dfc192012-01-17 15:11:37 +0100208 <<RoutInd:16, 0:13, GTinc:1, PCinc:1, SSNinc:1, Tail/binary>>.
209
210parse_sua_gt(Bin) ->
211 <<_:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, Remain/binary>> = Bin,
212 Number = parse_sua_gt_digits(NoDigits, Remain),
213 #global_title{gti = GTI, nature_of_addr_ind = NAI,
Harald Welte7e1c2612012-01-18 07:44:31 +0100214 trans_type = TransType,
Harald Welte50dfc192012-01-17 15:11:37 +0100215 numbering_plan = NumPlan,
216 phone_number = Number}.
217encode_sua_gt(Gt) when is_record(Gt, global_title) ->
218 #global_title{gti = GTI, nature_of_addr_ind = NAI,
Harald Welte7e1c2612012-01-18 07:44:31 +0100219 trans_type = TransType,
Harald Welte50dfc192012-01-17 15:11:37 +0100220 numbering_plan = NumPlan,
221 phone_number = Number} = Gt,
222 NoDigits = count_digits(Number),
223 DigitBin = encode_sua_gt_digits(Number),
224 <<0:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, DigitBin/binary>>.
225
226count_digits(Number) when is_integer(Number) ->
227 BcdList = osmo_util:int2digit_list(Number),
228 count_digits(BcdList);
229count_digits(Number) when is_list(Number) ->
230 length(Number).
231
232
233parse_sua_gt_digits(NoDigits, Remain) ->
234 % as opposed to ISUP/SCCP, we can have more than one nibble padding,
235 OddEven = NoDigits rem 1,
236 case OddEven of
237 0 ->
Harald Welte042a5792012-01-18 00:09:51 +0100238 ByteLen = NoDigits div 2;
Harald Welte50dfc192012-01-17 15:11:37 +0100239 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100240 ByteLen = NoDigits div 2 + 1
Harald Welte50dfc192012-01-17 15:11:37 +0100241 end,
242 <<Bin:ByteLen/binary, _/binary>> = Remain,
243 isup_codec:parse_isup_party(Bin, OddEven).
244encode_sua_gt_digits(Digits) when is_list(Digits); is_integer(Digits) ->
245 % Assume that overall option encoder will do the padding...
Harald Welte8e92c9a2012-01-18 00:25:26 +0100246 {Enc, _OddEven} = isup_codec:encode_isup_party(Digits),
247 Enc.
Harald Welte50dfc192012-01-17 15:11:37 +0100248
249parse_sua_pc(<<PC:32/big>>) ->
250 PC.
251encode_sua_pc(Pc) when is_integer(Pc) ->
252 <<Pc:32/big>>.
253
254parse_sua_ssn(<<_:24, SSN:8>>) ->
255 SSN.
256encode_sua_ssn(Ssn) when is_integer(Ssn) ->
257 <<0:24, Ssn:8>>.