blob: a683a87681a2ee5bdcc038d874784a1e7ca54989 [file] [log] [blame]
Harald Weltea68d96e2011-02-10 09:49:46 +01001% MAP masquerading application
2
3% (C) 2010-2011 by Harald Welte <laforge@gnumonks.org>
4% (C) 2010-2011 by On-Waves
5%
6% All Rights Reserved
7%
8% This program is free software; you can redistribute it and/or modify
9% it under the terms of the GNU General Public License as published by
10% the Free Software Foundation; either version 2 of the License, or
11% (at your option) any later version.
12%
13% This program is distributed in the hope that it will be useful,
14% but WITHOUT ANY WARRANTY; without even the implied warranty of
15% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16% GNU General Public License for more details.
17%
18% You should have received a copy of the GNU General Public License along
19% with this program; if not, write to the Free Software Foundation, Inc.,
20% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
21
22
23-module(map_masq).
24-author('Harald Welte <laforge@gnumonks.org>').
25%-compile(export_all).
26
27-export([mangle_map/1]).
28
29-define(PATCH_HLR_NUMBER, [1]).
30-define(PATCH_SGSN_NUMBER, [2]).
31-define(PATCH_SGSN_ADDRESS, [3]).
32-define(PATCH_VMSC_ADDRESS, [4]).
33-define(PATCH_GSMSCF_ADDRESS, [5]).
34
35-include_lib("osmo_map/include/map.hrl").
36
37mangle_msisdn(from_stp, _Opcode, AddrIn) ->
38 {ok, IntPfx} = application:get_env(intern_pfx),
39 mgw_nat:isup_party_internationalize(AddrIn, IntPfx).
40
41patch(#'SendRoutingInfoArg'{msisdn = Msisdn} = P) ->
42 AddrInDec = map_codec:parse_addr_string(Msisdn),
43 io:format("MSISDN IN = ~p~n", [AddrInDec]),
44 AddrOutDec = mangle_msisdn(from_stp, 22, AddrInDec),
45 io:format("MSISDN OUT = ~p~n", [AddrOutDec]),
46 AddrOutBin = map_codec:encode_addr_string(AddrOutDec),
47 P#'SendRoutingInfoArg'{msisdn = AddrOutBin};
48
49% patch a UpdateGprsLocationArg and replace SGSN number and SGSN address
50% !!! TESTING ONLY !!!
51patch(#'UpdateGprsLocationArg'{} = P) ->
52 P#'UpdateGprsLocationArg'{'sgsn-Number'= ?PATCH_SGSN_NUMBER,
53 'sgsn-Address' = ?PATCH_SGSN_ADDRESS};
54
55% Some other SGSN is sendingu us a GPRS location update. In the response,
56% we indicate teh HLR number, which we need to masquerade
57patch(#'UpdateGprsLocationRes'{} = P) ->
58 P#'UpdateGprsLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
59
60% Some other MSC/VLR is sendingu us a GSM location update. In the response,
61% we indicate teh HLR number, which we need to masquerade
62patch(#'UpdateLocationRes'{} = P) ->
63 P#'UpdateLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
64
65% HLR responds to VLR's MAP_RESTORE_REQ (i.e. it has lost information)
66patch(#'RestoreDataRes'{} = P) ->
67 P#'RestoreDataRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
68
69% HLR sends subscriber data to VLR/SGSN, including CAMEL info
70patch(#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=VlrCamel,
71 'sgsn-CAMEL-SubscriptionInfo'=SgsnCamel} = Arg) ->
72 Arg#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=patch(VlrCamel),
73 'sgsn-CAMEL-SubscriptionInfo'=patch(SgsnCamel)};
74
75% HLR sends subscriber data to gsmSCF
76patch(#'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=Csi} = P) ->
77 P#'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=patch(Csi)};
78
79patch(asn1_NOVALUE) ->
80 asn1_NOVALUE;
81
82% CAMEL related parsing
83
84% this is part of the InsertSubscriberData HLR -> VLR
85patch(#'VlrCamelSubscriptionInfo'{'o-CSI'=Ocsi, 'mo-sms-CSI'=MoSmsCsi,
86 'mt-sms-CSI'=MtSmsCsi, 'ss-CSI'=SsCsi} = P) ->
87 P#'VlrCamelSubscriptionInfo'{'o-CSI'=patch(Ocsi),
88 'mo-sms-CSI'=patch(MoSmsCsi),
89 'mt-sms-CSI'=patch(MtSmsCsi),
90 'ss-CSI'=patch(SsCsi)};
91
92% this is part of the InsertSubscriberData HLR -> SGSN
93patch(#'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=GprsCsi,
94 'mo-sms-CSI'=MoSmsCsi,
95 'mt-sms-CSI'=MtSmsCsi} = P) ->
96 P#'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=patch(GprsCsi),
97 'mo-sms-CSI'=patch(MoSmsCsi),
98 'mt-sms-CSI'=patch(MtSmsCsi)};
99
100% this is part of the Anytime Subscription Interrogation Result HLR->gsmSCF
101patch(#'CAMEL-SubscriptionInfo'{'o-CSI'=Ocsi,
102 'd-CSI'=Dcsi,
103 't-CSI'=Tcsi,
104 'vt-CSI'=Vtcsi,
105 %'tif-CSI'=Tifcsi,
106 'gprs-CSI'=GprsCsi,
107 'mo-sms-CSI'=MoSmsCsi,
108 'ss-CSI'=SsCsi,
109 'm-CSI'=Mcsi,
110 'mt-sms-CSI'=MtSmsCsi,
111 'mg-csi'=MgCsi,
112 'o-IM-CSI'=OimCsi,
113 'd-IM-CSI'=DimCsi,
114 'vt-IM-CSI'=VtImCsi} = P) ->
115 P#'CAMEL-SubscriptionInfo'{'o-CSI'=patch(Ocsi),
116 'd-CSI'=patch(Dcsi),
117 't-CSI'=patch(Tcsi),
118 'vt-CSI'=patch(Vtcsi),
119 'gprs-CSI'=patch(GprsCsi),
120 'mo-sms-CSI'=patch(MoSmsCsi),
121 'ss-CSI'=patch(SsCsi),
122 'm-CSI'=patch(Mcsi),
123 'mt-sms-CSI'=patch(MtSmsCsi),
124 'mg-csi'=patch(MgCsi),
125 'o-IM-CSI'=patch(OimCsi),
126 'd-IM-CSI'=patch(DimCsi),
127 'vt-IM-CSI'=patch(VtImCsi)};
128
129patch(#'T-CSI'{'t-BcsmCamelTDPDataList'=TdpList} = P) ->
130 P#'T-CSI'{'t-BcsmCamelTDPDataList'=patch_tBcsmCamelTDPDataList(TdpList)};
131patch(#'M-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
132 P#'M-CSI'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
133patch(#'MG-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
134 P#'MG-CSI'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
135patch(#'O-CSI'{'o-BcsmCamelTDPDataList'=TdpList} = P) ->
136 P#'O-CSI'{'o-BcsmCamelTDPDataList'=patch_oBcsmCamelTDPDataList(TdpList)};
137patch(#'D-CSI'{'dp-AnalysedInfoCriteriaList'=List} = P) ->
138 P#'D-CSI'{'dp-AnalysedInfoCriteriaList'=patch_AnInfoCritList(List)};
139patch(#'SMS-CSI'{'sms-CAMEL-TDP-DataList'=TdpList} = P) ->
140 P#'SMS-CSI'{'sms-CAMEL-TDP-DataList'=patch_SmsCamelTDPDataList(TdpList)};
141patch(#'SS-CSI'{'ss-CamelData'=Sscd} = P) ->
142 P#'SS-CSI'{'ss-CamelData'=patch(Sscd)};
143patch(#'GPRS-CSI'{'gprs-CamelTDPDataList'=TdpList} = P) ->
144 P#'GPRS-CSI'{'gprs-CamelTDPDataList'=patch_GprsCamelTDPDataList(TdpList)};
145patch(#'SS-CamelData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
146 P#'SS-CamelData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
147patch(#'O-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
148 P#'O-BcsmCamelTDPData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
149patch(#'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=GsmScfAddr} = P) ->
150 P#'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
151patch(#'GPRS-CamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
152 P#'GPRS-CamelTDPData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
153patch(#'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=GsmScfAddr} = P) ->
154 P#'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS}.
155
156patch_oBcsmCamelTDPDataList(List) ->
157 % we reverse the origianl list, as the tail recursive _acc function
158 % will invert the order of components again
159 patch_oBcsmCamelTDPDataList_acc(lists:reverse(List), []).
160patch_oBcsmCamelTDPDataList_acc([], NewList) -> NewList;
161patch_oBcsmCamelTDPDataList_acc([TdpData|Tail], NewList) ->
162 NewTdpData = patch(TdpData#'O-BcsmCamelTDPData'{}),
163 patch_oBcsmCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
164
165patch_tBcsmCamelTDPDataList(List) ->
166 % we reverse the origianl list, as the tail recursive _acc function
167 % will invert the order of components again
168 patch_tBcsmCamelTDPDataList_acc(lists:reverse(List), []).
169patch_tBcsmCamelTDPDataList_acc([], NewList) -> NewList;
170patch_tBcsmCamelTDPDataList_acc([TdpData|Tail], NewList) ->
171 NewTdpData = patch(TdpData#'T-BcsmCamelTDPData'{}),
172 patch_tBcsmCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
173
174patch_AnInfoCritList(List) ->
175 % we reverse the origianl list, as the tail recursive _acc function
176 % will invert the order of components again
177 patch_AnInfoCritList_acc(lists:reverse(List), []).
178patch_AnInfoCritList_acc([], NewList) -> NewList;
179patch_AnInfoCritList_acc([Crit|Tail], NewList) ->
180 NewCrit = patch(Crit#'DP-AnalysedInfoCriterium'{}),
181 patch_AnInfoCritList_acc(Tail, [NewCrit|NewList]).
182
183patch_GprsCamelTDPDataList(List) ->
184 % we reverse the origianl list, as the tail recursive _acc function
185 % will invert the order of components again
186 patch_GprsCamelTDPDataList_acc(lists:reverse(List), []).
187patch_GprsCamelTDPDataList_acc([], NewList) -> NewList;
188patch_GprsCamelTDPDataList_acc([TdpData|Tail], NewList) ->
189 NewTdpData = patch(TdpData#'GPRS-CamelTDPData'{}),
190 patch_GprsCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
191
192patch_SmsCamelTDPDataList(List) ->
193 % we reverse the origianl list, as the tail recursive _acc function
194 % will invert the order of components again
195 patch_SmsCamelTDPDataList_acc(lists:reverse(List), []).
196patch_SmsCamelTDPDataList_acc([], NewList) -> NewList;
197patch_SmsCamelTDPDataList_acc([TdpData|Tail], NewList) ->
198 NewTdpData = patch(TdpData#'SMS-CAMEL-TDP-Data'{}),
199 patch_GprsCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
200
201
202
203% process the Argument of a particular MAP invocation
204process_component_arg(OpCode, Arg) ->
205 case Arg of
206 asn1_NOVALUE -> Arg;
207 _ -> patch(Arg)
208 end.
209
210% recurse over all components
211handle_tcap_components(List) ->
212 % we reverse the origianl list, as the tail recursive _acc function
213 % will invert the order of components again
214 handle_tcap_components_acc(lists:reverse(List), []).
215handle_tcap_components_acc([], NewComponents) -> NewComponents;
216handle_tcap_components_acc([Component|Tail], NewComponents) ->
217 case Component of
218 {basicROS, {Primitive, Body}} ->
219 io:format("handle component ~p primitive ~n", [Component]),
220 case Body of
221 % BEGIN
222 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
223 argument=Arg} ->
224 NewArg = process_component_arg(OpCode, Arg),
225 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{argument=NewArg};
226 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg}} ->
227 NewArg = process_component_arg(OpCode, Arg),
228 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
229 #'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg}} ->
230 NewArg = process_component_arg(OpCode, Arg),
231 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
232 % END
233 #'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
234 argument=Arg} ->
235 NewArg = process_component_arg(OpCode, Arg),
236 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{argument=NewArg};
237 #'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg}} ->
238 NewArg = process_component_arg(OpCode, Arg),
239 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
240 #'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg}} ->
241 NewArg = process_component_arg(OpCode, Arg),
242 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
243 % CONTINUE
244 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
245 argument=Arg} ->
246 NewArg = process_component_arg(OpCode, Arg),
247 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{argument=NewArg};
248 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg}} ->
249 NewArg = process_component_arg(OpCode, Arg),
250 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
251 #'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg}} ->
252 NewArg = process_component_arg(OpCode, Arg),
253 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
254 _ ->
255 NewBody = Body
256 end,
257 %NewBody = setelement(5, Body, NewArg)
258 NewComponent = {basicROS, {Primitive, NewBody}};
259 _ ->
260 NewComponent = Component
261 end,
262 io:format("=> modified component ~p~n", [NewComponent]),
263 handle_tcap_components_acc(Tail, [NewComponent|NewComponents]).
264
265
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100266% Erlang asn1rt has this strange property that all incoming EXTERNAL types are
267% converted from the 1990 version into the 1994 version. The latter does not
268% preserve the encoding (octet string, single ASN1 type, ...). During encoding,
269% it then uses the OCTTET-STRING encoding, which is different from the MAP
270% customary single-ASN1-type format.
Harald Weltec506fe52011-02-10 13:09:44 +0100271asn1_EXTERNAL1994_fixup({'EXTERNAL', DirRef, IndRef, Data}) when is_list(Data);is_binary(Data) ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100272 % our trick is as follows: we simply convert back to 1990 format, and explicitly
273 % set the single-ASN1-type encoding. asn1rt:s 'enc_EXTERNAL'() will detect this
274 #'EXTERNAL'{'direct-reference' = DirRef, 'indirect-reference' = IndRef,
275 'encoding' = {'single-ASN1-type', Data}};
276asn1_EXTERNAL1994_fixup(Foo) ->
277 Foo.
278
279
280handle_tcap_dialogue(Foo = {'EXTERNAL', DirRef, IndRef, Data}) ->
281 asn1_EXTERNAL1994_fixup(Foo);
282handle_tcap_dialogue(Foo) ->
283 Foo.
284
Harald Weltea68d96e2011-02-10 09:49:46 +0100285
286%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
287% Actual mangling of the decoded MAP messages
288%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
289mangle_map({Type, TcapMsgDec}) ->
290 case {Type, TcapMsgDec} of
291 {'unidirectional', #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dialg,
292 components=Components}} ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100293 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100294 NewComponents = handle_tcap_components(Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100295 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_unidirectional'{dialoguePortion=NewDialg, components=NewComponents};
Harald Weltea68d96e2011-02-10 09:49:46 +0100296 {'begin', #'MapSpecificPDUs_begin'{components=Components}} ->
297 NewComponents = handle_tcap_components(Components),
298 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_begin'{components=NewComponents};
299 {'continue', #'MapSpecificPDUs_continue'{dialoguePortion=Dialg, components=Components}} ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100300 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100301 NewComponents = handle_tcap_components(Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100302 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_continue'{dialoguePortion=NewDialg, components=NewComponents};
Harald Weltea68d96e2011-02-10 09:49:46 +0100303 {'end', #'MapSpecificPDUs_end'{components=Components}} ->
304 NewComponents = handle_tcap_components(Components),
305 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_end'{components=NewComponents};
306 _ ->
307 NewTcapMsgDec = TcapMsgDec
308 end,
309 io:format("new TcapMsgDec ~p~n", [NewTcapMsgDec]),
310 {Type, NewTcapMsgDec}.
311