blob: 06797ad0ec611524b2c339961908aebac19b3581 [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
Harald Weltef9629642011-02-10 20:44:46 +010027-export([mangle_map/2, config_update/0]).
Harald Weltea68d96e2011-02-10 09:49:46 +010028
29-include_lib("osmo_map/include/map.hrl").
Harald Weltef9629642011-02-10 20:44:46 +010030-include_lib("osmo_ss7/include/isup.hrl").
31
32% Use the MAP address translation table to alter an ISDN-Address-String
Harald Welte29e589f2011-02-25 15:17:57 +010033patch_map_isdn_addr(_From, asn1_NOVALUE, _Type) ->
Harald Weltef9629642011-02-10 20:44:46 +010034 asn1_NOVALUE;
Harald Welte29e589f2011-02-25 15:17:57 +010035patch_map_isdn_addr(From, AddrIn, Type) when is_binary(AddrIn) ->
36 patch_map_isdn_addr(From, binary_to_list(AddrIn), Type);
37patch_map_isdn_addr(From, AddrIn, Type) when is_list(AddrIn) ->
Harald Weltef9629642011-02-10 20:44:46 +010038 % obtain some configuration data
39 {ok, Tbl} = application:get_env(map_rewrite_table),
40 {ok, IntPfx} = application:get_env(intern_pfx),
41 % Decode the list of octets into an party_number
42 AddrInDec = map_codec:parse_addr_string(AddrIn),
43 % First we always internationalize the address
Harald Welte6a33c1e2011-02-10 21:40:40 +010044 AddrInIntl = mgw_nat:isup_party_internationalize(AddrInDec, IntPfx),
Harald Weltef9629642011-02-10 20:44:46 +010045 % And then patch/replace the address digits
46 DigitsIn = AddrInIntl#party_number.phone_number,
Harald Welte29e589f2011-02-25 15:17:57 +010047 DigitsOut = patch_map_isdn_digits(From, DigitsIn, Type, Tbl),
Harald Weltef9629642011-02-10 20:44:46 +010048 AddrOutIntl = AddrInIntl#party_number{phone_number = DigitsOut},
49 if AddrOutIntl == AddrInDec ->
50 ok;
51 true ->
52 io:format("Translating MAP-ISDN-Addess ~p ~p -> ~p~n",
53 [Type, AddrInDec, AddrOutIntl])
54 end,
Harald Welte62aa7c62011-02-10 22:52:01 +010055 map_codec:encode_addr_string(AddrOutIntl).
Harald Weltef9629642011-02-10 20:44:46 +010056
Harald Welte29e589f2011-02-25 15:17:57 +010057patch_map_isdn_digits(_From, AddrIn, _Type, []) ->
Harald Weltef9629642011-02-10 20:44:46 +010058 AddrIn;
Harald Welte29e589f2011-02-25 15:17:57 +010059patch_map_isdn_digits(From, AddrIn, TypeIn, [Head|Tail]) ->
Harald Weltef9629642011-02-10 20:44:46 +010060 case Head of
61 {TypeIn, _,_, MscSide, StpSide} ->
62 if AddrIn == MscSide ->
63 StpSide;
64 AddrIn == StpSide ->
65 MscSide;
66 true ->
Harald Welte29e589f2011-02-25 15:17:57 +010067 patch_map_isdn_digits(From, AddrIn, TypeIn, Tail)
Harald Weltef9629642011-02-10 20:44:46 +010068 end;
69 _ ->
Harald Welte29e589f2011-02-25 15:17:57 +010070 patch_map_isdn_digits(From, AddrIn, TypeIn, Tail)
Harald Weltef9629642011-02-10 20:44:46 +010071 end.
Harald Weltea68d96e2011-02-10 09:49:46 +010072
73mangle_msisdn(from_stp, _Opcode, AddrIn) ->
74 {ok, IntPfx} = application:get_env(intern_pfx),
Harald Welte6a33c1e2011-02-10 21:40:40 +010075 mgw_nat:isup_party_internationalize(AddrIn, IntPfx).
Harald Weltea68d96e2011-02-10 09:49:46 +010076
Harald Welte449a3172011-02-10 15:06:27 +010077% Someobdy inquires on Routing Info for a MS (from HLR)
Harald Welte29e589f2011-02-25 15:17:57 +010078patch(From = from_stp, #'SendRoutingInfoArg'{msisdn = Msisdn,'gmsc-OrGsmSCF-Address'=GmscAddr} = P) ->
Harald Weltee78474e2011-02-10 21:04:52 +010079 % First Translate the MSISDN into international
Harald Weltea68d96e2011-02-10 09:49:46 +010080 AddrInDec = map_codec:parse_addr_string(Msisdn),
81 io:format("MSISDN IN = ~p~n", [AddrInDec]),
Harald Welte29e589f2011-02-25 15:17:57 +010082 AddrOutDec = mangle_msisdn(From, 22, AddrInDec),
Harald Weltea68d96e2011-02-10 09:49:46 +010083 io:format("MSISDN OUT = ~p~n", [AddrOutDec]),
84 AddrOutBin = map_codec:encode_addr_string(AddrOutDec),
Harald Weltee78474e2011-02-10 21:04:52 +010085 % Second, try to masquerade the G-MSC
86 GmscInDec = map_codec:parse_addr_string(GmscAddr),
87 case sccp_masq:lookup_masq_addr(orig, GmscInDec#party_number.phone_number) of
88 undef ->
89 GmscOut = GmscAddr;
90 GmscOutDigits ->
91 GmscOutDec = GmscInDec#party_number{phone_number = GmscOutDigits},
92 GmscOut = map_codec:encode_addr_string(GmscOutDec)
93 end,
94 P#'SendRoutingInfoArg'{msisdn = AddrOutBin, 'gmsc-OrGsmSCF-Address' = GmscOut};
Harald Weltea68d96e2011-02-10 09:49:46 +010095
Harald Welte449a3172011-02-10 15:06:27 +010096% HLR responds with Routing Info for a MS
Harald Welte29e589f2011-02-25 15:17:57 +010097patch(From, #'SendRoutingInfoRes'{extendedRoutingInfo = ExtRoutInfo,
Holger Hans Peter Freyther016e3062011-02-21 22:04:38 +010098 subscriberInfo = SubscriberInfo,
Harald Welte449a3172011-02-10 15:06:27 +010099 'vmsc-Address' = VmscAddress} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100100 VmscAddrOut = patch_map_isdn_addr(From, VmscAddress, msc),
101 P#'SendRoutingInfoRes'{extendedRoutingInfo = patch(From, ExtRoutInfo),
102 'subscriberInfo' = patch(From, SubscriberInfo),
Harald Weltef9629642011-02-10 20:44:46 +0100103 'vmsc-Address' = VmscAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100104patch(From, #'CamelRoutingInfo'{gmscCamelSubscriptionInfo = GmscCamelSI} = P) ->
105 P#'CamelRoutingInfo'{gmscCamelSubscriptionInfo = patch(From, GmscCamelSI)};
106patch(From, {camelRoutingInfo, CRI}) ->
107 {camelRoutingInfo, patch(From, CRI)};
108patch(From, {routingInfo, RI}) ->
109 {routingInfo, patch(From, RI)};
Harald Welte449a3172011-02-10 15:06:27 +0100110
Harald Weltef9629642011-02-10 20:44:46 +0100111% HLR responds to inquiring MSC indicating the current serving MSC number
Harald Welte29e589f2011-02-25 15:17:57 +0100112patch(From, #'RoutingInfoForSM-Res'{locationInfoWithLMSI = LocInf} = P) ->
113 P#'RoutingInfoForSM-Res'{locationInfoWithLMSI = patch(From, LocInf)};
114patch(From, #'LocationInfoWithLMSI'{'networkNode-Number' = NetNodeNr} = P) ->
115 NetNodeNrOut = patch_map_isdn_addr(From, NetNodeNr, msc),
Harald Weltef9629642011-02-10 20:44:46 +0100116 P#'LocationInfoWithLMSI'{'networkNode-Number' = NetNodeNrOut};
117
Harald Weltedf81bdd2011-02-10 17:21:26 +0100118% patch the roaming number as it is sent from HLR to G-MSC (SRI Resp)
Harald Welte29e589f2011-02-25 15:17:57 +0100119patch(_From, {roamingNumber, RoamNumTBCD}) ->
Harald Weltedf81bdd2011-02-10 17:21:26 +0100120 RoamNumIn = map_codec:parse_addr_string(RoamNumTBCD),
121 io:format("Roaming Number IN = ~p~n", [RoamNumIn]),
122 {ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
123 {ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
Harald Welte6a33c1e2011-02-10 21:40:40 +0100124 RoamNumOut = mgw_nat:isup_party_replace_prefix(RoamNumIn, MsrnPfxMsc, MsrnPfxStp),
Harald Weltedf81bdd2011-02-10 17:21:26 +0100125 io:format("Roaming Number OUT = ~p~n", [RoamNumOut]),
126 RoamNumOutTBCD = map_codec:encode_addr_string(RoamNumOut),
127 {roamingNumber, RoamNumOutTBCD};
128
Harald Welte449a3172011-02-10 15:06:27 +0100129
Harald Weltea68d96e2011-02-10 09:49:46 +0100130% patch a UpdateGprsLocationArg and replace SGSN number and SGSN address
131% !!! TESTING ONLY !!!
Harald Welte29e589f2011-02-25 15:17:57 +0100132patch(From, #'UpdateGprsLocationArg'{'sgsn-Number' = SgsnNum,
Harald Weltef9629642011-02-10 20:44:46 +0100133 'sgsn-Address' = SgsnAddr} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100134 SgsnNumOut = patch_map_isdn_addr(From, SgsnNum, sgsn),
Harald Weltef9629642011-02-10 20:44:46 +0100135 P#'UpdateGprsLocationArg'{'sgsn-Number'= SgsnNumOut,
136 'sgsn-Address' = SgsnAddr};
Harald Weltea68d96e2011-02-10 09:49:46 +0100137
138% Some other SGSN is sendingu us a GPRS location update. In the response,
139% we indicate teh HLR number, which we need to masquerade
Harald Welte29e589f2011-02-25 15:17:57 +0100140patch(From, #'UpdateGprsLocationRes'{'hlr-Number' = HlrNum} = P) ->
141 HlrNumOut = patch_map_isdn_addr(From, HlrNum, hlr),
Harald Weltef9629642011-02-10 20:44:46 +0100142 P#'UpdateGprsLocationRes'{'hlr-Number' = HlrNumOut};
Harald Weltea68d96e2011-02-10 09:49:46 +0100143
144% Some other MSC/VLR is sendingu us a GSM location update. In the response,
145% we indicate teh HLR number, which we need to masquerade
Harald Welte29e589f2011-02-25 15:17:57 +0100146patch(From, #'UpdateLocationRes'{'hlr-Number' = HlrNum} = P) ->
147 HlrNumOut = patch_map_isdn_addr(From, HlrNum, hlr),
Harald Weltef9629642011-02-10 20:44:46 +0100148 P#'UpdateLocationRes'{'hlr-Number' = HlrNumOut};
Harald Weltea68d96e2011-02-10 09:49:46 +0100149
150% HLR responds to VLR's MAP_RESTORE_REQ (i.e. it has lost information)
Harald Welte29e589f2011-02-25 15:17:57 +0100151patch(From, #'RestoreDataRes'{'hlr-Number' = HlrNum} = P) ->
152 HlrNumOut = patch_map_isdn_addr(From, HlrNum, hlr),
Harald Weltef9629642011-02-10 20:44:46 +0100153 P#'RestoreDataRes'{'hlr-Number' = HlrNumOut};
Harald Weltea68d96e2011-02-10 09:49:46 +0100154
155% HLR sends subscriber data to VLR/SGSN, including CAMEL info
Harald Welte29e589f2011-02-25 15:17:57 +0100156patch(From, #'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=VlrCamel,
Harald Weltea68d96e2011-02-10 09:49:46 +0100157 'sgsn-CAMEL-SubscriptionInfo'=SgsnCamel} = Arg) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100158 Arg#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=patch(From, VlrCamel),
159 'sgsn-CAMEL-SubscriptionInfo'=patch(From, SgsnCamel)};
Harald Weltea68d96e2011-02-10 09:49:46 +0100160
161% HLR sends subscriber data to gsmSCF
Harald Welte29e589f2011-02-25 15:17:57 +0100162patch(From, #'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=Csi} = P) ->
163 P#'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=patch(From, Csi)};
Harald Weltea68d96e2011-02-10 09:49:46 +0100164
Harald Welte29e589f2011-02-25 15:17:57 +0100165patch(From, asn1_NOVALUE) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100166 asn1_NOVALUE;
167
168% CAMEL related parsing
169
Harald Welte449a3172011-02-10 15:06:27 +0100170% this is part of the SRI Response (HLR->GMSC)
Harald Welte29e589f2011-02-25 15:17:57 +0100171patch(From, #'GmscCamelSubscriptionInfo'{'o-CSI'=Ocsi, 't-CSI'=Tcsi,
Harald Welte449a3172011-02-10 15:06:27 +0100172 'd-csi'=Dcsi} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100173 P#'GmscCamelSubscriptionInfo'{'o-CSI'=patch(From, Ocsi),
174 't-CSI'=patch(From, Tcsi),
175 'd-csi'=patch(From, Dcsi)};
Harald Welte449a3172011-02-10 15:06:27 +0100176
Harald Weltea68d96e2011-02-10 09:49:46 +0100177% this is part of the InsertSubscriberData HLR -> VLR
Harald Welte29e589f2011-02-25 15:17:57 +0100178patch(From, #'VlrCamelSubscriptionInfo'{'o-CSI'=Ocsi, 'mo-sms-CSI'=MoSmsCsi,
Harald Weltea68d96e2011-02-10 09:49:46 +0100179 'mt-sms-CSI'=MtSmsCsi, 'ss-CSI'=SsCsi} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100180 P#'VlrCamelSubscriptionInfo'{'o-CSI'=patch(From, Ocsi),
181 'mo-sms-CSI'=patch(From, MoSmsCsi),
182 'mt-sms-CSI'=patch(From, MtSmsCsi),
183 'ss-CSI'=patch(From, SsCsi)};
Harald Weltea68d96e2011-02-10 09:49:46 +0100184
185% this is part of the InsertSubscriberData HLR -> SGSN
Harald Welte29e589f2011-02-25 15:17:57 +0100186patch(From, #'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=GprsCsi,
Harald Weltea68d96e2011-02-10 09:49:46 +0100187 'mo-sms-CSI'=MoSmsCsi,
188 'mt-sms-CSI'=MtSmsCsi} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100189 P#'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=patch(From, GprsCsi),
190 'mo-sms-CSI'=patch(From, MoSmsCsi),
191 'mt-sms-CSI'=patch(From, MtSmsCsi)};
Harald Weltea68d96e2011-02-10 09:49:46 +0100192
193% this is part of the Anytime Subscription Interrogation Result HLR->gsmSCF
Harald Welte29e589f2011-02-25 15:17:57 +0100194patch(From, #'CAMEL-SubscriptionInfo'{'o-CSI'=Ocsi,
Harald Weltea68d96e2011-02-10 09:49:46 +0100195 'd-CSI'=Dcsi,
196 't-CSI'=Tcsi,
197 'vt-CSI'=Vtcsi,
198 %'tif-CSI'=Tifcsi,
199 'gprs-CSI'=GprsCsi,
200 'mo-sms-CSI'=MoSmsCsi,
201 'ss-CSI'=SsCsi,
202 'm-CSI'=Mcsi,
203 'mt-sms-CSI'=MtSmsCsi,
204 'mg-csi'=MgCsi,
205 'o-IM-CSI'=OimCsi,
206 'd-IM-CSI'=DimCsi,
207 'vt-IM-CSI'=VtImCsi} = P) ->
Harald Welte29e589f2011-02-25 15:17:57 +0100208 P#'CAMEL-SubscriptionInfo'{'o-CSI'=patch(From, Ocsi),
209 'd-CSI'=patch(From, Dcsi),
210 't-CSI'=patch(From, Tcsi),
211 'vt-CSI'=patch(From, Vtcsi),
212 'gprs-CSI'=patch(From, GprsCsi),
213 'mo-sms-CSI'=patch(From, MoSmsCsi),
214 'ss-CSI'=patch(From, SsCsi),
215 'm-CSI'=patch(From, Mcsi),
216 'mt-sms-CSI'=patch(From, MtSmsCsi),
217 'mg-csi'=patch(From, MgCsi),
218 'o-IM-CSI'=patch(From, OimCsi),
219 'd-IM-CSI'=patch(From, DimCsi),
220 'vt-IM-CSI'=patch(From, VtImCsi)};
Harald Weltea68d96e2011-02-10 09:49:46 +0100221
Harald Welte29e589f2011-02-25 15:17:57 +0100222patch(From, #'T-CSI'{'t-BcsmCamelTDPDataList'=TdpList} = P) ->
223 P#'T-CSI'{'t-BcsmCamelTDPDataList'=patch_tBcsmCamelTDPDataList(From, TdpList)};
224patch(From, #'M-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
225 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100226 P#'M-CSI'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100227patch(From, #'MG-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
228 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100229 P#'MG-CSI'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100230patch(From, #'O-CSI'{'o-BcsmCamelTDPDataList'=TdpList} = P) ->
231 P#'O-CSI'{'o-BcsmCamelTDPDataList'=patch_oBcsmCamelTDPDataList(From, TdpList)};
232patch(From, #'D-CSI'{'dp-AnalysedInfoCriteriaList'=List} = P) ->
233 P#'D-CSI'{'dp-AnalysedInfoCriteriaList'=patch_AnInfoCritList(From, List)};
234patch(From, #'SMS-CSI'{'sms-CAMEL-TDP-DataList'=TdpList} = P) ->
235 P#'SMS-CSI'{'sms-CAMEL-TDP-DataList'=patch_SmsCamelTDPDataList(From, TdpList)};
236patch(From, #'SS-CSI'{'ss-CamelData'=Sscd} = P) ->
237 P#'SS-CSI'{'ss-CamelData'=patch(From, Sscd)};
238patch(From, #'GPRS-CSI'{'gprs-CamelTDPDataList'=TdpList} = P) ->
239 P#'GPRS-CSI'{'gprs-CamelTDPDataList'=patch_GprsCamelTDPDataList(From, TdpList)};
240patch(From, #'SS-CamelData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
241 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100242 P#'SS-CamelData'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100243patch(From, #'O-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
244 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100245 P#'O-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100246patch(From, #'T-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
247 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Holger Hans Peter Freyther60e0fb22011-02-21 21:02:08 +0100248 P#'T-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100249patch(From, #'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=GsmScfAddr} = P) ->
250 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100251 P#'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100252patch(From, #'GPRS-CamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
253 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100254 P#'GPRS-CamelTDPData'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100255patch(From, #'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=GsmScfAddr} = P) ->
256 GsmScfAddrOut = patch_map_isdn_addr(From, GsmScfAddr, scf),
Harald Weltef9629642011-02-10 20:44:46 +0100257 P#'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=GsmScfAddrOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100258patch(From, #'SubscriberInfo'{'locationInformation'=LocInformation} = P) ->
259 P#'SubscriberInfo'{'locationInformation'=patch(From, LocInformation)};
260patch(From, #'LocationInformation'{'vlr-number'=VlrNumber} = P) ->
261 VlrNumberOut = patch_map_isdn_addr(From, VlrNumber, vlr),
Holger Hans Peter Freyther016e3062011-02-21 22:04:38 +0100262 P#'LocationInformation'{'vlr-number'=VlrNumberOut};
Harald Welte29e589f2011-02-25 15:17:57 +0100263patch(From, #'MO-ForwardSM-Arg'{'sm-RP-DA'=SC} = P) ->
264 NewSC = patch_scaddr(From, SC),
Holger Hans Peter Freythere86edbd2011-02-22 23:24:55 +0100265 P#'MO-ForwardSM-Arg'{'sm-RP-DA'=NewSC};
Holger Hans Peter Freyther016e3062011-02-21 22:04:38 +0100266
Harald Welte29e589f2011-02-25 15:17:57 +0100267patch(_From, Default) ->
Harald Weltec7523622011-02-10 14:42:31 +0100268 Default.
Harald Weltea68d96e2011-02-10 09:49:46 +0100269
Holger Hans Peter Freythere86edbd2011-02-22 23:24:55 +0100270%rewrite the serviceCentreAddressDA
Harald Welte29e589f2011-02-25 15:17:57 +0100271patch_scaddr(From, {serviceCentreAddressDA,Ar}) ->
272 NewAddr = patch_map_isdn_addr(From, Ar, smsCDA),
Holger Hans Peter Freythere86edbd2011-02-22 23:24:55 +0100273 {serviceCentreAddressDA,NewAddr};
Harald Welte29e589f2011-02-25 15:17:57 +0100274patch_scaddr(From, Default) ->
Holger Hans Peter Freythere86edbd2011-02-22 23:24:55 +0100275 Default.
276
Harald Welte29e589f2011-02-25 15:17:57 +0100277patch_oBcsmCamelTDPDataList(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100278 % we reverse the origianl list, as the tail recursive _acc function
279 % will invert the order of components again
Harald Welte29e589f2011-02-25 15:17:57 +0100280 patch_oBcsmCamelTDPDataList_acc(From, lists:reverse(List), []).
281patch_oBcsmCamelTDPDataList_acc(From, [], NewList) -> NewList;
282patch_oBcsmCamelTDPDataList_acc(From, [TdpData|Tail], NewList) ->
283 NewTdpData = patch(From, TdpData#'O-BcsmCamelTDPData'{}),
284 patch_oBcsmCamelTDPDataList_acc(From, Tail, [NewTdpData|NewList]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100285
Harald Welte29e589f2011-02-25 15:17:57 +0100286patch_tBcsmCamelTDPDataList(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100287 % we reverse the origianl list, as the tail recursive _acc function
288 % will invert the order of components again
Harald Welte29e589f2011-02-25 15:17:57 +0100289 patch_tBcsmCamelTDPDataList_acc(From, lists:reverse(List), []).
290patch_tBcsmCamelTDPDataList_acc(From, [], NewList) -> NewList;
291patch_tBcsmCamelTDPDataList_acc(From, [TdpData|Tail], NewList) ->
292 NewTdpData = patch(From, TdpData#'T-BcsmCamelTDPData'{}),
293 patch_tBcsmCamelTDPDataList_acc(From, Tail, [NewTdpData|NewList]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100294
Harald Welte29e589f2011-02-25 15:17:57 +0100295patch_AnInfoCritList(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100296 % we reverse the origianl list, as the tail recursive _acc function
297 % will invert the order of components again
Harald Welte29e589f2011-02-25 15:17:57 +0100298 patch_AnInfoCritList_acc(From, lists:reverse(List), []).
299patch_AnInfoCritList_acc(From, [], NewList) -> NewList;
300patch_AnInfoCritList_acc(From, [Crit|Tail], NewList) ->
301 NewCrit = patch(From, Crit#'DP-AnalysedInfoCriterium'{}),
302 patch_AnInfoCritList_acc(From, Tail, [NewCrit|NewList]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100303
Harald Welte29e589f2011-02-25 15:17:57 +0100304patch_GprsCamelTDPDataList(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100305 % we reverse the origianl list, as the tail recursive _acc function
306 % will invert the order of components again
Harald Welte29e589f2011-02-25 15:17:57 +0100307 patch_GprsCamelTDPDataList_acc(From, lists:reverse(List), []).
308patch_GprsCamelTDPDataList_acc(_From, [], NewList) -> NewList;
309patch_GprsCamelTDPDataList_acc(From, [TdpData|Tail], NewList) ->
310 NewTdpData = patch(From, TdpData#'GPRS-CamelTDPData'{}),
311 patch_GprsCamelTDPDataList_acc(From, Tail, [NewTdpData|NewList]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100312
Harald Welte29e589f2011-02-25 15:17:57 +0100313patch_SmsCamelTDPDataList(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100314 % we reverse the origianl list, as the tail recursive _acc function
315 % will invert the order of components again
Harald Welte29e589f2011-02-25 15:17:57 +0100316 patch_SmsCamelTDPDataList_acc(From, lists:reverse(List), []).
317patch_SmsCamelTDPDataList_acc(From, [], NewList) -> NewList;
318patch_SmsCamelTDPDataList_acc(From, [TdpData|Tail], NewList) ->
319 NewTdpData = patch(From, TdpData#'SMS-CAMEL-TDP-Data'{}),
320 patch_GprsCamelTDPDataList_acc(From, Tail, [NewTdpData|NewList]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100321
322
323
324% process the Argument of a particular MAP invocation
Harald Welte29e589f2011-02-25 15:17:57 +0100325process_component_arg(From, OpCode, Arg) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100326 case Arg of
327 asn1_NOVALUE -> Arg;
Harald Welte29e589f2011-02-25 15:17:57 +0100328 _ -> patch(From,Arg)
Harald Weltea68d96e2011-02-10 09:49:46 +0100329 end.
330
331% recurse over all components
Harald Welte2cc831f2011-02-10 18:36:02 +0100332handle_tcap_components(_From, asn1_NOVALUE) ->
Harald Welte17f64742011-02-10 18:29:59 +0100333 asn1_NOVALUE;
Harald Welte2cc831f2011-02-10 18:36:02 +0100334handle_tcap_components(From, List) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100335 % we reverse the origianl list, as the tail recursive _acc function
336 % will invert the order of components again
Harald Welte2cc831f2011-02-10 18:36:02 +0100337 handle_tcap_components_acc(From, lists:reverse(List), []).
338handle_tcap_components_acc(_From, [], NewComponents) -> NewComponents;
339handle_tcap_components_acc(From, [Component|Tail], NewComponents) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100340 case Component of
341 {basicROS, {Primitive, Body}} ->
342 io:format("handle component ~p primitive ~n", [Component]),
343 case Body of
344 % BEGIN
345 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
346 argument=Arg} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100347 NewArg = process_component_arg(From, OpCode, Arg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100348 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100349 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100350 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100351 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
352 #'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100353 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100354 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100355 % END
356 #'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
357 argument=Arg} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100358 NewArg = process_component_arg(From, OpCode, Arg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100359 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100360 #'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100361 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100362 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
363 #'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100364 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100365 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100366 % CONTINUE
367 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
368 argument=Arg} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100369 NewArg = process_component_arg(From, OpCode, Arg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100370 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100371 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100372 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100373 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
374 #'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100375 NewArg = process_component_arg(From, OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100376 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100377 _ ->
378 NewBody = Body
379 end,
380 %NewBody = setelement(5, Body, NewArg)
381 NewComponent = {basicROS, {Primitive, NewBody}};
382 _ ->
383 NewComponent = Component
384 end,
385 io:format("=> modified component ~p~n", [NewComponent]),
Harald Welte2cc831f2011-02-10 18:36:02 +0100386 handle_tcap_components_acc(From, Tail, [NewComponent|NewComponents]).
Harald Weltea68d96e2011-02-10 09:49:46 +0100387
388
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100389% Erlang asn1rt has this strange property that all incoming EXTERNAL types are
390% converted from the 1990 version into the 1994 version. The latter does not
391% preserve the encoding (octet string, single ASN1 type, ...). During encoding,
392% it then uses the OCTTET-STRING encoding, which is different from the MAP
393% customary single-ASN1-type format.
Harald Weltec506fe52011-02-10 13:09:44 +0100394asn1_EXTERNAL1994_fixup({'EXTERNAL', DirRef, IndRef, Data}) when is_list(Data);is_binary(Data) ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100395 % our trick is as follows: we simply convert back to 1990 format, and explicitly
396 % set the single-ASN1-type encoding. asn1rt:s 'enc_EXTERNAL'() will detect this
397 #'EXTERNAL'{'direct-reference' = DirRef, 'indirect-reference' = IndRef,
398 'encoding' = {'single-ASN1-type', Data}};
399asn1_EXTERNAL1994_fixup(Foo) ->
400 Foo.
401
402
Harald Welte2cc831f2011-02-10 18:36:02 +0100403handle_tcap_dialogue(_From, Foo = {'EXTERNAL', DirRef, IndRef, Data}) ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100404 asn1_EXTERNAL1994_fixup(Foo);
Harald Welte2cc831f2011-02-10 18:36:02 +0100405handle_tcap_dialogue(_From, Foo) ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100406 Foo.
407
Harald Weltea68d96e2011-02-10 09:49:46 +0100408
409%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
410% Actual mangling of the decoded MAP messages
411%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Harald Welte2cc831f2011-02-10 18:36:02 +0100412mangle_map(From, {Type, TcapMsgDec}) ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100413 case {Type, TcapMsgDec} of
414 {'unidirectional', #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dialg,
415 components=Components}} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100416 NewDialg = handle_tcap_dialogue(From, Dialg),
417 NewComponents = handle_tcap_components(From, Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100418 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_unidirectional'{dialoguePortion=NewDialg, components=NewComponents};
Harald Welte29c5f402011-02-10 13:24:49 +0100419 {'begin', #'MapSpecificPDUs_begin'{dialoguePortion=Dialg, components=Components}} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100420 NewDialg = handle_tcap_dialogue(From, Dialg),
421 NewComponents = handle_tcap_components(From, Components),
Harald Welte29c5f402011-02-10 13:24:49 +0100422 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_begin'{dialoguePortion=NewDialg, components=NewComponents};
Harald Weltea68d96e2011-02-10 09:49:46 +0100423 {'continue', #'MapSpecificPDUs_continue'{dialoguePortion=Dialg, components=Components}} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100424 NewDialg = handle_tcap_dialogue(From, Dialg),
425 NewComponents = handle_tcap_components(From, Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100426 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_continue'{dialoguePortion=NewDialg, components=NewComponents};
Harald Welte29c5f402011-02-10 13:24:49 +0100427 {'end', #'MapSpecificPDUs_end'{dialoguePortion=Dialg, components=Components}} ->
Harald Welte2cc831f2011-02-10 18:36:02 +0100428 NewDialg = handle_tcap_dialogue(From, Dialg),
429 NewComponents = handle_tcap_components(From, Components),
Harald Welte29c5f402011-02-10 13:24:49 +0100430 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_end'{dialoguePortion=NewDialg, components=NewComponents};
431 %{_, #'Abort'{reason=Reason} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100432 _ ->
433 NewTcapMsgDec = TcapMsgDec
434 end,
Harald Welte29c5f402011-02-10 13:24:49 +0100435 io:format("new TcapMsgDec (Type=~p) ~p~n", [Type, NewTcapMsgDec]),
Harald Weltea68d96e2011-02-10 09:49:46 +0100436 {Type, NewTcapMsgDec}.
437
Harald Weltef9629642011-02-10 20:44:46 +0100438
439% Configuration file has changed, re-generate internal data structures
440config_update() ->
441 % (re-)generate the MAP Address rewrite table
Harald Welte6009f6e2011-02-10 21:41:50 +0100442 {ok, MapRewriteTbl} = application:get_env(mgw_nat, map_rewrite_table),
Harald Weltef9629642011-02-10 20:44:46 +0100443 MapRewriteTblOut = generate_rewrite_table(MapRewriteTbl),
Harald Welte6009f6e2011-02-10 21:41:50 +0100444 application:set_env(mgw_nat, map_rewrite_table, MapRewriteTblOut),
Harald Weltef9629642011-02-10 20:44:46 +0100445 %{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
446 %{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
447 %{ok, IntPfx} = application:get_env(intern_pfx),
448 ok.
449
450% Generate the full MAP address rewrite table
451generate_rewrite_table(List) when is_list(List) ->
452 generate_rewrite_table(List, []).
453generate_rewrite_table([], OutList) ->
454 io:format("(Re)generated MAP ISDN-Address rewrite table: ~p~n", [OutList]),
455 OutList;
456generate_rewrite_table([Head|Tail], OutList) ->
457 NewItem = generate_rewrite_entry(Head),
458 generate_rewrite_table(Tail, [NewItem|OutList]).
459
460% Generate a MAP Address rewrite table entry
461generate_rewrite_entry({Name, MscSideInt, StpSideInt}) ->
462 MscSideList = osmo_util:int2digit_list(MscSideInt),
463 StpSideList = osmo_util:int2digit_list(StpSideInt),
464 {Name, MscSideInt, StpSideInt, MscSideList, StpSideList}.