blob: 9c121282daaf68f4a35083233e1ec1f9b4e46a45 [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/>.
19
20% FIXME: this currently only supports connection-less SCCP
21
22-module(sua_sccp_conv).
23-author('Harald Welte <laforge@gnumonks.org>').
24
25-include("sua.hrl").
Harald Welte92e783d2012-04-01 19:52:01 +020026-include("xua.hrl").
Harald Welte50dfc192012-01-17 15:11:37 +010027-include("sccp.hrl").
28
29-export([sua_to_sccp/1, sccp_to_sua/1]).
30
Harald Welte92e783d2012-04-01 19:52:01 +020031sua_to_sccp(M=#xua_msg{msg_class = Class, msg_type = Type}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010032 sua_to_sccp(Class, Type, M).
33sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDT, Sua) ->
34 Params = sua_to_sccp_params(Sua),
35 #sccp_msg{msg_type = ?SCCP_MSGT_UDT,
36 parameters = Params};
37sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDR, Sua) ->
38 Params = sua_to_sccp_params(Sua),
39 #sccp_msg{msg_type = ?SCCP_MSGT_UDTS,
40 parameters = Params}.
41
Harald Welte99efaf92012-01-18 14:11:23 +010042sccp_to_sua(#sccp_msg{msg_type = Type, parameters = Params}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010043 sccp_to_sua(Type, Params).
44sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDT;
45 Type == ?SCCP_MSGT_XUDT;
46 Type == ?SCCP_MSGT_LUDT ->
Harald Welte8e92c9a2012-01-18 00:25:26 +010047 Opts = sccp_to_sua_params(Type, Params),
Harald Welte92e783d2012-04-01 19:52:01 +020048 #xua_msg{version = 1, msg_class = ?SUA_MSGC_CL,
Harald Welte8e92c9a2012-01-18 00:25:26 +010049 msg_type = ?SUA_CL_CLDT, payload = Opts};
Harald Welte50dfc192012-01-17 15:11:37 +010050sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDTS;
51 Type == ?SCCP_MSGT_XUDTS;
52 Type == ?SCCP_MSGT_LUDTS ->
53 Opts = sccp_to_sua_params(Params),
Harald Welte92e783d2012-04-01 19:52:01 +020054 #xua_msg{version=1, msg_class = ?SUA_MSGC_CL,
Harald Welte8e92c9a2012-01-18 00:25:26 +010055 msg_type = ?SUA_CL_CLDR, payload = Opts}.
Harald Welte50dfc192012-01-17 15:11:37 +010056
57
58% CLDT parameters:
59% ?SUA_IEI_ROUTE_CTX, ?SUA_IEI_PROTO_CLASS, ?SUA_IEI_SRC_ADDR,
60% ?SUA_IEI_DEST_ADDR, ?SUA_IEI_SEQ_CTRL, ?SUA_IEI_S7_HOP_CTR,
61% ?SUA_IEI_IMPORTANCE, ?SUA_IEI_MSG_PRIO, ?SUA_IEI_CORR_ID,
62% ?SUA_IEI_SEGMENTATION, ?SUA_IEI_DATA
63
Harald Welte92e783d2012-04-01 19:52:01 +020064sua_to_sccp_params(#xua_msg{msg_class=Class, msg_type=Type, payload=Payload}) ->
Harald Welte50dfc192012-01-17 15:11:37 +010065 sua_to_sccp_params(Class, Type, Payload).
66sua_to_sccp_params(Class, Type, Payload) ->
67 sua_to_sccp_params(Class, Type, Payload, []).
Harald Welte99efaf92012-01-18 14:11:23 +010068sua_to_sccp_params(_Class, _Type, [], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +010069 List;
Harald Welte042a5792012-01-18 00:09:51 +010070sua_to_sccp_params(Class, Type, [{ParTag, {_Len, ParVal}}|Remain], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +010071 NewPars = sua_to_sccp_param(Class, Type, ParTag, ParVal),
72 sua_to_sccp_params(Class, Type, Remain, List ++ NewPars).
73
74% convert an individual SUA parameter to a SCCP option
75sua_to_sccp_param(_, _, ?SUA_IEI_PROTO_CLASS, Remain) ->
Harald Welte99efaf92012-01-18 14:11:23 +010076 <<_:24, PCOpt:4, _:2, Class:2>> = Remain,
77 [{protocol_class, {Class, PCOpt}}];
Harald Welte50dfc192012-01-17 15:11:37 +010078sua_to_sccp_param(_, _, ?SUA_IEI_SRC_ADDR, Remain) ->
79 Addr = sua_to_sccp_addr(Remain),
Harald Welte7e1c2612012-01-18 07:44:31 +010080 [{calling_party_addr, Addr}];
Harald Welte50dfc192012-01-17 15:11:37 +010081sua_to_sccp_param(_, _, ?SUA_IEI_DEST_ADDR, Remain) ->
82 Addr = sua_to_sccp_addr(Remain),
Harald Welte7e1c2612012-01-18 07:44:31 +010083 [{called_party_addr, Addr}];
Harald Welte99efaf92012-01-18 14:11:23 +010084sua_to_sccp_param(_, _, ?SUA_IEI_SEQ_CTRL, _Remain) ->
85 % If we were to translate to a N-UNITDATA.req, we could map
86 % this, but there is no mapping to a SCCP message...
87 [];
Harald Welte50dfc192012-01-17 15:11:37 +010088sua_to_sccp_param(_, _, ?SUA_IEI_S7_HOP_CTR, Remain) ->
89 <<_:24, HopCtr:8>> = Remain,
90 [{?SCCP_PNC_HOP_COUNTER, HopCtr}];
91sua_to_sccp_param(_, _, ?SUA_IEI_IMPORTANCE, Remain) ->
92 <<_:24, Imp:8>> = Remain,
93 [{?SCCP_PNC_IMPORTANCE, Imp}];
94sua_to_sccp_param(_, _, ?SUA_IEI_DATA, Remain) ->
Harald Welte7e1c2612012-01-18 07:44:31 +010095 [{user_data, Remain}];
Harald Welte99efaf92012-01-18 14:11:23 +010096sua_to_sccp_param(_, _, ?SUA_IEI_ROUTE_CTX, _Remain) ->
Harald Welte042a5792012-01-18 00:09:51 +010097 %FIXME: what to do with routing context?
98 [].
Harald Welte50dfc192012-01-17 15:11:37 +010099
100sccp_to_sua_params(#sccp_msg{msg_type=Type, parameters=Params}) ->
101 sccp_to_sua_params(Type, Params).
102sccp_to_sua_params(Type, Params) when is_list(Params) ->
103 sccp_to_sua_params(Type, Params, []).
Harald Welte99efaf92012-01-18 14:11:23 +0100104sccp_to_sua_params(_Type, [], List) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100105 List;
106sccp_to_sua_params(Type, [{ParTag, ParVal}|Tail], List) ->
107 NewPars = sccp_to_sua_param(Type, ParTag, ParVal),
108 sccp_to_sua_params(Type, Tail, List ++ NewPars).
109
Harald Welte99efaf92012-01-18 14:11:23 +0100110sccp_to_sua_param(_, protocol_class, {Opt, Class}) ->
111 [{?SUA_IEI_PROTO_CLASS, <<0:24, Opt:4, 0:2, Class:2>>}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100112sccp_to_sua_param(_, calling_party_addr, Addr) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100113 AddrSua = sccp_to_sua_addr(Addr),
114 [{?SUA_IEI_SRC_ADDR, AddrSua}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100115sccp_to_sua_param(_, called_party_addr, Addr) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100116 AddrSua = sccp_to_sua_addr(Addr),
117 [{?SUA_IEI_DEST_ADDR, AddrSua}];
Harald Welte50dfc192012-01-17 15:11:37 +0100118sccp_to_sua_param(_, ?SCCP_PNC_HOP_COUNTER, Hop) ->
119 [{?SUA_IEI_S7_HOP_CTR, <<0:24, Hop:8>>}];
120sccp_to_sua_param(_, ?SCCP_PNC_IMPORTANCE, Imp) ->
121 [{?SUA_IEI_IMPORTANCE, <<0:24, Imp:8>>}];
Harald Welte7e1c2612012-01-18 07:44:31 +0100122sccp_to_sua_param(_, user_data, Data) ->
Harald Welte50dfc192012-01-17 15:11:37 +0100123 [{?SUA_IEI_DATA, Data}].
124
125sua_to_sccp_addr(SuaBin) ->
126 <<RoutInd:16, _:13, GTinc:1, PCinc:1, SSNinc:1, Remain/binary>> = SuaBin,
127 ParList = addr_pars_to_list(Remain),
128 case GTinc of
129 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100130 {_, GTopt} = proplists:get_value(?SUA_IEI_GT, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100131 GT = parse_sua_gt(GTopt);
132 0 ->
133 GT = undefined
134 end,
135 case PCinc of
136 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100137 {_, PCopt} = proplists:get_value(?SUA_IEI_PC, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100138 PC = parse_sua_pc(PCopt);
139 0 ->
140 PC = undefined
141 end,
142 case SSNinc of
143 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100144 {_, SSNopt} = proplists:get_value(?SUA_IEI_SSN, ParList),
Harald Welte50dfc192012-01-17 15:11:37 +0100145 SSN = parse_sua_ssn(SSNopt);
146 0 ->
147 SSN = undefined
148 end,
149 case RoutInd of
150 ?SUA_RI_GT ->
151 RoutSSN = 0;
152 ?SUA_RI_SSN_PC ->
153 RoutSSN = 1
154 end,
155 #sccp_addr{route_on_ssn = RoutSSN, point_code = PC, ssn = SSN, global_title = GT}.
156
157addr_pars_to_list(Bin) ->
Harald Welte92e783d2012-04-01 19:52:01 +0200158 xua_codec:parse_xua_opts(Bin).
Harald Welte50dfc192012-01-17 15:11:37 +0100159
160sccp_to_sua_addr(Addr) when is_record(Addr, sccp_addr) ->
161 #sccp_addr{route_on_ssn = RoutOnSsn, point_code = PC, ssn = SSN,
162 global_title = GT} = Addr,
163 case GT of
164 #global_title{} ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100165 GTopt = [{?SUA_IEI_GT, encode_sua_gt(GT)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100166 GTinc = 1;
167 _ ->
168 GTopt = [],
169 GTinc = 0
170 end,
171 case PC of
172 Int when is_integer(Int) ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100173 PCopt = [{?SUA_IEI_PC, encode_sua_pc(PC)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100174 PCinc = 1;
175 _ ->
176 PCopt = [],
177 PCinc = 0
178 end,
179 case SSN of
180 Int2 when is_integer(Int2) ->
Harald Welte8e92c9a2012-01-18 00:25:26 +0100181 SSNopt = [{?SUA_IEI_SSN, encode_sua_ssn(SSN)}],
Harald Welte50dfc192012-01-17 15:11:37 +0100182 SSNinc = 1;
183 _ ->
184 SSNopt = [],
185 SSNinc = 0
186 end,
187 case RoutOnSsn of
188 0 ->
189 RoutInd = ?SUA_RI_GT;
190 1 ->
191 RoutInd = ?SUA_RI_SSN_PC
192 end,
Harald Welte92e783d2012-04-01 19:52:01 +0200193 Tail = xua_codec:encode_xua_opts(GTopt ++ PCopt ++ SSNopt),
Harald Welte50dfc192012-01-17 15:11:37 +0100194 <<RoutInd:16, 0:13, GTinc:1, PCinc:1, SSNinc:1, Tail/binary>>.
195
196parse_sua_gt(Bin) ->
197 <<_:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, Remain/binary>> = Bin,
198 Number = parse_sua_gt_digits(NoDigits, Remain),
199 #global_title{gti = GTI, nature_of_addr_ind = NAI,
Harald Welte7e1c2612012-01-18 07:44:31 +0100200 trans_type = TransType,
Harald Welte50dfc192012-01-17 15:11:37 +0100201 numbering_plan = NumPlan,
202 phone_number = Number}.
203encode_sua_gt(Gt) when is_record(Gt, global_title) ->
204 #global_title{gti = GTI, nature_of_addr_ind = NAI,
Harald Welte7e1c2612012-01-18 07:44:31 +0100205 trans_type = TransType,
Harald Welte50dfc192012-01-17 15:11:37 +0100206 numbering_plan = NumPlan,
207 phone_number = Number} = Gt,
208 NoDigits = count_digits(Number),
209 DigitBin = encode_sua_gt_digits(Number),
210 <<0:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, DigitBin/binary>>.
211
212count_digits(Number) when is_integer(Number) ->
213 BcdList = osmo_util:int2digit_list(Number),
214 count_digits(BcdList);
215count_digits(Number) when is_list(Number) ->
216 length(Number).
217
218
219parse_sua_gt_digits(NoDigits, Remain) ->
220 % as opposed to ISUP/SCCP, we can have more than one nibble padding,
221 OddEven = NoDigits rem 1,
222 case OddEven of
223 0 ->
Harald Welte042a5792012-01-18 00:09:51 +0100224 ByteLen = NoDigits div 2;
Harald Welte50dfc192012-01-17 15:11:37 +0100225 1 ->
Harald Welte042a5792012-01-18 00:09:51 +0100226 ByteLen = NoDigits div 2 + 1
Harald Welte50dfc192012-01-17 15:11:37 +0100227 end,
228 <<Bin:ByteLen/binary, _/binary>> = Remain,
229 isup_codec:parse_isup_party(Bin, OddEven).
230encode_sua_gt_digits(Digits) when is_list(Digits); is_integer(Digits) ->
231 % Assume that overall option encoder will do the padding...
Harald Welte8e92c9a2012-01-18 00:25:26 +0100232 {Enc, _OddEven} = isup_codec:encode_isup_party(Digits),
233 Enc.
Harald Welte50dfc192012-01-17 15:11:37 +0100234
235parse_sua_pc(<<PC:32/big>>) ->
236 PC.
237encode_sua_pc(Pc) when is_integer(Pc) ->
238 <<Pc:32/big>>.
239
240parse_sua_ssn(<<_:24, SSN:8>>) ->
241 SSN.
242encode_sua_ssn(Ssn) when is_integer(Ssn) ->
243 <<0:24, Ssn:8>>.