blob: 2483ba57fd0b88da170d39114594cc1e96c348f6 [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").
26-include("sccp.hrl").
27
28-export([sua_to_sccp/1, sccp_to_sua/1]).
29
30sua_to_sccp(M=#sua_msg{msg_class = Class, msg_type = Type}) ->
31 sua_to_sccp(Class, Type, M).
32sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDT, Sua) ->
33 Params = sua_to_sccp_params(Sua),
34 #sccp_msg{msg_type = ?SCCP_MSGT_UDT,
35 parameters = Params};
36sua_to_sccp(?SUA_MSGC_CL, ?SUA_CL_CLDR, Sua) ->
37 Params = sua_to_sccp_params(Sua),
38 #sccp_msg{msg_type = ?SCCP_MSGT_UDTS,
39 parameters = Params}.
40
41sccp_to_sua(M=#sccp_msg{msg_type = Type, parameters = Params}) ->
42 sccp_to_sua(Type, Params).
43sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDT;
44 Type == ?SCCP_MSGT_XUDT;
45 Type == ?SCCP_MSGT_LUDT ->
46 Opts = sccp_to_sua_params(Params),
47 #sua_msg{msg_class = ?SUA_MSGC_CL, msg_type = ?SUA_CL_CLDT,
48 payload = Opts};
49sccp_to_sua(Type, Params) when Type == ?SCCP_MSGT_UDTS;
50 Type == ?SCCP_MSGT_XUDTS;
51 Type == ?SCCP_MSGT_LUDTS ->
52 Opts = sccp_to_sua_params(Params),
53 #sua_msg{msg_class = ?SUA_MSGC_CL, msg_type = ?SUA_CL_CLDR,
54 payload = Opts}.
55
56
57% CLDT parameters:
58% ?SUA_IEI_ROUTE_CTX, ?SUA_IEI_PROTO_CLASS, ?SUA_IEI_SRC_ADDR,
59% ?SUA_IEI_DEST_ADDR, ?SUA_IEI_SEQ_CTRL, ?SUA_IEI_S7_HOP_CTR,
60% ?SUA_IEI_IMPORTANCE, ?SUA_IEI_MSG_PRIO, ?SUA_IEI_CORR_ID,
61% ?SUA_IEI_SEGMENTATION, ?SUA_IEI_DATA
62
63sua_to_sccp_params(#sua_msg{msg_class=Class, msg_type=Type, payload=Payload}) ->
64 sua_to_sccp_params(Class, Type, Payload).
65sua_to_sccp_params(Class, Type, Payload) ->
66 sua_to_sccp_params(Class, Type, Payload, []).
67sua_to_sccp_params(Class, Type, [], List) ->
68 List;
69sua_to_sccp_params(Class, Type, [{ParTag, ParVal}|Remain], List) ->
70 NewPars = sua_to_sccp_param(Class, Type, ParTag, ParVal),
71 sua_to_sccp_params(Class, Type, Remain, List ++ NewPars).
72
73% convert an individual SUA parameter to a SCCP option
74sua_to_sccp_param(_, _, ?SUA_IEI_PROTO_CLASS, Remain) ->
75 <<_:24, RetErr:1, _:5, Class:2>> = Remain,
76 [{?SCCP_PNC_PROTOCOL_CLASS, Class}];
77sua_to_sccp_param(_, _, ?SUA_IEI_SRC_ADDR, Remain) ->
78 Addr = sua_to_sccp_addr(Remain),
79 [{?SCCP_PNC_CALLING_PARTY_ADDRESS, Addr}];
80sua_to_sccp_param(_, _, ?SUA_IEI_DEST_ADDR, Remain) ->
81 Addr = sua_to_sccp_addr(Remain),
82 [{?SCCP_PNC_CALLED_PARTY_ADDRESS, Addr}];
83sua_to_sccp_param(_, _, ?SUA_IEI_SEQ_CTRL, Remain) ->
84 [{?SCCP_PNC_SEQUENCING, Remain}];
85sua_to_sccp_param(_, _, ?SUA_IEI_S7_HOP_CTR, Remain) ->
86 <<_:24, HopCtr:8>> = Remain,
87 [{?SCCP_PNC_HOP_COUNTER, HopCtr}];
88sua_to_sccp_param(_, _, ?SUA_IEI_IMPORTANCE, Remain) ->
89 <<_:24, Imp:8>> = Remain,
90 [{?SCCP_PNC_IMPORTANCE, Imp}];
91sua_to_sccp_param(_, _, ?SUA_IEI_DATA, Remain) ->
92 [{?SCCP_PNC_DATA, Remain}].
93
94sccp_to_sua_params(#sccp_msg{msg_type=Type, parameters=Params}) ->
95 sccp_to_sua_params(Type, Params).
96sccp_to_sua_params(Type, Params) when is_list(Params) ->
97 sccp_to_sua_params(Type, Params, []).
98sccp_to_sua_params(Type, [], List) ->
99 List;
100sccp_to_sua_params(Type, [{ParTag, ParVal}|Tail], List) ->
101 NewPars = sccp_to_sua_param(Type, ParTag, ParVal),
102 sccp_to_sua_params(Type, Tail, List ++ NewPars).
103
104sccp_to_sua_param(_, ?SCCP_PNC_PROTOCOL_CLASS, Class) ->
105 [{?SUA_IEI_PROTO_CLASS, <<0:24, 0:1, 0:5, Class:2>>}];
106sccp_to_sua_param(_, ?SCCP_PNC_CALLING_PARTY_ADDRESS, Addr) ->
107 AddrSua = sccp_to_sua_addr(Addr),
108 [{?SUA_IEI_SRC_ADDR, AddrSua}];
109sccp_to_sua_param(_, ?SCCP_PNC_CALLED_PARTY_ADDRESS, Addr) ->
110 AddrSua = sccp_to_sua_addr(Addr),
111 [{?SUA_IEI_DEST_ADDR, AddrSua}];
112sccp_to_sua_param(_, ?SCCP_PNC_SEQUENCING, Par) ->
113 [{?SUA_IEI_SEQ_CTRL, Par}];
114sccp_to_sua_param(_, ?SCCP_PNC_HOP_COUNTER, Hop) ->
115 [{?SUA_IEI_S7_HOP_CTR, <<0:24, Hop:8>>}];
116sccp_to_sua_param(_, ?SCCP_PNC_IMPORTANCE, Imp) ->
117 [{?SUA_IEI_IMPORTANCE, <<0:24, Imp:8>>}];
118sccp_to_sua_param(_, ?SCCP_PNC_DATA, Data) ->
119 [{?SUA_IEI_DATA, Data}].
120
121sua_to_sccp_addr(SuaBin) ->
122 <<RoutInd:16, _:13, GTinc:1, PCinc:1, SSNinc:1, Remain/binary>> = SuaBin,
123 ParList = addr_pars_to_list(Remain),
124 case GTinc of
125 1 ->
126 GTopt = proplists:get_value(?SUA_IEI_GT, ParList),
127 GT = parse_sua_gt(GTopt);
128 0 ->
129 GT = undefined
130 end,
131 case PCinc of
132 1 ->
133 PCopt = proplists:get_value(?SUA_IEI_PC, ParList),
134 PC = parse_sua_pc(PCopt);
135 0 ->
136 PC = undefined
137 end,
138 case SSNinc of
139 1 ->
140 SSNopt = proplists:get_value(?SUA_IEI_SSN, ParList),
141 SSN = parse_sua_ssn(SSNopt);
142 0 ->
143 SSN = undefined
144 end,
145 case RoutInd of
146 ?SUA_RI_GT ->
147 RoutSSN = 0;
148 ?SUA_RI_SSN_PC ->
149 RoutSSN = 1
150 end,
151 #sccp_addr{route_on_ssn = RoutSSN, point_code = PC, ssn = SSN, global_title = GT}.
152
153addr_pars_to_list(Bin) ->
154 sua_codec:parse_xua_opts(Bin).
155
156sccp_to_sua_addr(Addr) when is_record(Addr, sccp_addr) ->
157 #sccp_addr{route_on_ssn = RoutOnSsn, point_code = PC, ssn = SSN,
158 global_title = GT} = Addr,
159 case GT of
160 #global_title{} ->
161 GTopt = encode_sua_gt(GT),
162 GTinc = 1;
163 _ ->
164 GTopt = [],
165 GTinc = 0
166 end,
167 case PC of
168 Int when is_integer(Int) ->
169 PCopt = encode_sua_pc(PC),
170 PCinc = 1;
171 _ ->
172 PCopt = [],
173 PCinc = 0
174 end,
175 case SSN of
176 Int2 when is_integer(Int2) ->
177 SSNopt = encode_sua_ssn(SSN),
178 SSNinc = 1;
179 _ ->
180 SSNopt = [],
181 SSNinc = 0
182 end,
183 case RoutOnSsn of
184 0 ->
185 RoutInd = ?SUA_RI_GT;
186 1 ->
187 RoutInd = ?SUA_RI_SSN_PC
188 end,
189 Tail = sua_codec:encode_xua_opts(GTopt ++ PCopt ++ SSNopt),
190 <<RoutInd:16, 0:13, GTinc:1, PCinc:1, SSNinc:1, Tail/binary>>.
191
192parse_sua_gt(Bin) ->
193 <<_:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, Remain/binary>> = Bin,
194 Number = parse_sua_gt_digits(NoDigits, Remain),
195 #global_title{gti = GTI, nature_of_addr_ind = NAI,
196 trans_type = TransType, encoding = fixme,
197 numbering_plan = NumPlan,
198 phone_number = Number}.
199encode_sua_gt(Gt) when is_record(Gt, global_title) ->
200 #global_title{gti = GTI, nature_of_addr_ind = NAI,
201 trans_type = TransType, encoding = Encoding,
202 numbering_plan = NumPlan,
203 phone_number = Number} = Gt,
204 NoDigits = count_digits(Number),
205 DigitBin = encode_sua_gt_digits(Number),
206 <<0:24, GTI:8, NoDigits:8, TransType:8, NumPlan:8, NAI:8, DigitBin/binary>>.
207
208count_digits(Number) when is_integer(Number) ->
209 BcdList = osmo_util:int2digit_list(Number),
210 count_digits(BcdList);
211count_digits(Number) when is_list(Number) ->
212 length(Number).
213
214
215parse_sua_gt_digits(NoDigits, Remain) ->
216 % as opposed to ISUP/SCCP, we can have more than one nibble padding,
217 OddEven = NoDigits rem 1,
218 case OddEven of
219 0 ->
220 ByteLen = NoDigits/2;
221 1 ->
222 ByteLen = NoDigits/2 + 1
223 end,
224 <<Bin:ByteLen/binary, _/binary>> = Remain,
225 isup_codec:parse_isup_party(Bin, OddEven).
226encode_sua_gt_digits(Digits) when is_list(Digits); is_integer(Digits) ->
227 % Assume that overall option encoder will do the padding...
228 isup_codec:encode_isup_party(Digits).
229
230parse_sua_pc(<<PC:32/big>>) ->
231 PC.
232encode_sua_pc(Pc) when is_integer(Pc) ->
233 <<Pc:32/big>>.
234
235parse_sua_ssn(<<_:24, SSN:8>>) ->
236 SSN.
237encode_sua_ssn(Ssn) when is_integer(Ssn) ->
238 <<0:24, Ssn:8>>.