blob: 1edc4a25a50bc4c1b35aa94e617e5b1461c6b268 [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
Harald Welte449a3172011-02-10 15:06:27 +010041% Someobdy inquires on Routing Info for a MS (from HLR)
Harald Weltea68d96e2011-02-10 09:49:46 +010042patch(#'SendRoutingInfoArg'{msisdn = Msisdn} = P) ->
43 AddrInDec = map_codec:parse_addr_string(Msisdn),
44 io:format("MSISDN IN = ~p~n", [AddrInDec]),
45 AddrOutDec = mangle_msisdn(from_stp, 22, AddrInDec),
46 io:format("MSISDN OUT = ~p~n", [AddrOutDec]),
47 AddrOutBin = map_codec:encode_addr_string(AddrOutDec),
48 P#'SendRoutingInfoArg'{msisdn = AddrOutBin};
49
Harald Welte449a3172011-02-10 15:06:27 +010050% HLR responds with Routing Info for a MS
51patch(#'SendRoutingInfoRes'{extendedRoutingInfo = ExtRoutInfo,
52 'vmsc-Address' = VmscAddress} = P) ->
53 P#'SendRoutingInfoRes'{extendedRoutingInfo = patch(ExtRoutInfo),
54 'vmsc-Address' = ?PATCH_VMSC_ADDRESS};
55patch(#'CamelRoutingInfo'{gmscCamelSubscriptionInfo = GmscCamelSI} = P) ->
56 P#'CamelRoutingInfo'{gmscCamelSubscriptionInfo = patch(GmscCamelSI)};
57patch({camelRoutingInfo, CRI}) ->
58 {camelRoutingInfo, patch(CRI)};
59patch({routingInfo, RI}) ->
60 {routingInfo, patch(RI)};
61
Harald Weltedf81bdd2011-02-10 17:21:26 +010062% patch the roaming number as it is sent from HLR to G-MSC (SRI Resp)
63patch({roamingNumber, RoamNumTBCD}) ->
64 RoamNumIn = map_codec:parse_addr_string(RoamNumTBCD),
65 io:format("Roaming Number IN = ~p~n", [RoamNumIn]),
66 {ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
67 {ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
Harald Welte17f64742011-02-10 18:29:59 +010068 RoamNumOut = mgw_nat:isup_party_replace_prefix(RoamNumIn, MsrnPfxMsc, MsrnPfxStp),
Harald Weltedf81bdd2011-02-10 17:21:26 +010069 io:format("Roaming Number OUT = ~p~n", [RoamNumOut]),
70 RoamNumOutTBCD = map_codec:encode_addr_string(RoamNumOut),
71 {roamingNumber, RoamNumOutTBCD};
72
Harald Welte449a3172011-02-10 15:06:27 +010073
Harald Weltea68d96e2011-02-10 09:49:46 +010074% patch a UpdateGprsLocationArg and replace SGSN number and SGSN address
75% !!! TESTING ONLY !!!
76patch(#'UpdateGprsLocationArg'{} = P) ->
77 P#'UpdateGprsLocationArg'{'sgsn-Number'= ?PATCH_SGSN_NUMBER,
78 'sgsn-Address' = ?PATCH_SGSN_ADDRESS};
79
80% Some other SGSN is sendingu us a GPRS location update. In the response,
81% we indicate teh HLR number, which we need to masquerade
82patch(#'UpdateGprsLocationRes'{} = P) ->
83 P#'UpdateGprsLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
84
85% Some other MSC/VLR is sendingu us a GSM location update. In the response,
86% we indicate teh HLR number, which we need to masquerade
87patch(#'UpdateLocationRes'{} = P) ->
88 P#'UpdateLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
89
90% HLR responds to VLR's MAP_RESTORE_REQ (i.e. it has lost information)
91patch(#'RestoreDataRes'{} = P) ->
92 P#'RestoreDataRes'{'hlr-Number' = ?PATCH_HLR_NUMBER};
93
94% HLR sends subscriber data to VLR/SGSN, including CAMEL info
95patch(#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=VlrCamel,
96 'sgsn-CAMEL-SubscriptionInfo'=SgsnCamel} = Arg) ->
97 Arg#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo'=patch(VlrCamel),
98 'sgsn-CAMEL-SubscriptionInfo'=patch(SgsnCamel)};
99
100% HLR sends subscriber data to gsmSCF
101patch(#'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=Csi} = P) ->
102 P#'AnyTimeSubscriptionInterrogationRes'{'camel-SubscriptionInfo'=patch(Csi)};
103
104patch(asn1_NOVALUE) ->
105 asn1_NOVALUE;
106
107% CAMEL related parsing
108
Harald Welte449a3172011-02-10 15:06:27 +0100109% this is part of the SRI Response (HLR->GMSC)
110patch(#'GmscCamelSubscriptionInfo'{'o-CSI'=Ocsi, 't-CSI'=Tcsi,
111 'd-csi'=Dcsi} = P) ->
112 P#'GmscCamelSubscriptionInfo'{'o-CSI'=patch(Ocsi),
113 't-CSI'=patch(Tcsi),
114 'd-csi'=patch(Dcsi)};
115
Harald Weltea68d96e2011-02-10 09:49:46 +0100116% this is part of the InsertSubscriberData HLR -> VLR
117patch(#'VlrCamelSubscriptionInfo'{'o-CSI'=Ocsi, 'mo-sms-CSI'=MoSmsCsi,
118 'mt-sms-CSI'=MtSmsCsi, 'ss-CSI'=SsCsi} = P) ->
119 P#'VlrCamelSubscriptionInfo'{'o-CSI'=patch(Ocsi),
120 'mo-sms-CSI'=patch(MoSmsCsi),
121 'mt-sms-CSI'=patch(MtSmsCsi),
122 'ss-CSI'=patch(SsCsi)};
123
124% this is part of the InsertSubscriberData HLR -> SGSN
125patch(#'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=GprsCsi,
126 'mo-sms-CSI'=MoSmsCsi,
127 'mt-sms-CSI'=MtSmsCsi} = P) ->
128 P#'SGSN-CAMEL-SubscriptionInfo'{'gprs-CSI'=patch(GprsCsi),
129 'mo-sms-CSI'=patch(MoSmsCsi),
130 'mt-sms-CSI'=patch(MtSmsCsi)};
131
132% this is part of the Anytime Subscription Interrogation Result HLR->gsmSCF
133patch(#'CAMEL-SubscriptionInfo'{'o-CSI'=Ocsi,
134 'd-CSI'=Dcsi,
135 't-CSI'=Tcsi,
136 'vt-CSI'=Vtcsi,
137 %'tif-CSI'=Tifcsi,
138 'gprs-CSI'=GprsCsi,
139 'mo-sms-CSI'=MoSmsCsi,
140 'ss-CSI'=SsCsi,
141 'm-CSI'=Mcsi,
142 'mt-sms-CSI'=MtSmsCsi,
143 'mg-csi'=MgCsi,
144 'o-IM-CSI'=OimCsi,
145 'd-IM-CSI'=DimCsi,
146 'vt-IM-CSI'=VtImCsi} = P) ->
147 P#'CAMEL-SubscriptionInfo'{'o-CSI'=patch(Ocsi),
148 'd-CSI'=patch(Dcsi),
149 't-CSI'=patch(Tcsi),
150 'vt-CSI'=patch(Vtcsi),
151 'gprs-CSI'=patch(GprsCsi),
152 'mo-sms-CSI'=patch(MoSmsCsi),
153 'ss-CSI'=patch(SsCsi),
154 'm-CSI'=patch(Mcsi),
155 'mt-sms-CSI'=patch(MtSmsCsi),
156 'mg-csi'=patch(MgCsi),
157 'o-IM-CSI'=patch(OimCsi),
158 'd-IM-CSI'=patch(DimCsi),
159 'vt-IM-CSI'=patch(VtImCsi)};
160
161patch(#'T-CSI'{'t-BcsmCamelTDPDataList'=TdpList} = P) ->
162 P#'T-CSI'{'t-BcsmCamelTDPDataList'=patch_tBcsmCamelTDPDataList(TdpList)};
163patch(#'M-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
164 P#'M-CSI'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
165patch(#'MG-CSI'{'gsmSCF-Address'=GsmScfAddr} = P) ->
166 P#'MG-CSI'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
167patch(#'O-CSI'{'o-BcsmCamelTDPDataList'=TdpList} = P) ->
168 P#'O-CSI'{'o-BcsmCamelTDPDataList'=patch_oBcsmCamelTDPDataList(TdpList)};
169patch(#'D-CSI'{'dp-AnalysedInfoCriteriaList'=List} = P) ->
170 P#'D-CSI'{'dp-AnalysedInfoCriteriaList'=patch_AnInfoCritList(List)};
171patch(#'SMS-CSI'{'sms-CAMEL-TDP-DataList'=TdpList} = P) ->
172 P#'SMS-CSI'{'sms-CAMEL-TDP-DataList'=patch_SmsCamelTDPDataList(TdpList)};
173patch(#'SS-CSI'{'ss-CamelData'=Sscd} = P) ->
174 P#'SS-CSI'{'ss-CamelData'=patch(Sscd)};
175patch(#'GPRS-CSI'{'gprs-CamelTDPDataList'=TdpList} = P) ->
176 P#'GPRS-CSI'{'gprs-CamelTDPDataList'=patch_GprsCamelTDPDataList(TdpList)};
177patch(#'SS-CamelData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
178 P#'SS-CamelData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
179patch(#'O-BcsmCamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
180 P#'O-BcsmCamelTDPData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
181patch(#'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=GsmScfAddr} = P) ->
182 P#'SMS-CAMEL-TDP-Data'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
183patch(#'GPRS-CamelTDPData'{'gsmSCF-Address'=GsmScfAddr} = P) ->
184 P#'GPRS-CamelTDPData'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
185patch(#'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=GsmScfAddr} = P) ->
Harald Weltec7523622011-02-10 14:42:31 +0100186 P#'DP-AnalysedInfoCriterium'{'gsmSCF-Address'=?PATCH_GSMSCF_ADDRESS};
187patch(Default) ->
188 Default.
Harald Weltea68d96e2011-02-10 09:49:46 +0100189
190patch_oBcsmCamelTDPDataList(List) ->
191 % we reverse the origianl list, as the tail recursive _acc function
192 % will invert the order of components again
193 patch_oBcsmCamelTDPDataList_acc(lists:reverse(List), []).
194patch_oBcsmCamelTDPDataList_acc([], NewList) -> NewList;
195patch_oBcsmCamelTDPDataList_acc([TdpData|Tail], NewList) ->
196 NewTdpData = patch(TdpData#'O-BcsmCamelTDPData'{}),
197 patch_oBcsmCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
198
199patch_tBcsmCamelTDPDataList(List) ->
200 % we reverse the origianl list, as the tail recursive _acc function
201 % will invert the order of components again
202 patch_tBcsmCamelTDPDataList_acc(lists:reverse(List), []).
203patch_tBcsmCamelTDPDataList_acc([], NewList) -> NewList;
204patch_tBcsmCamelTDPDataList_acc([TdpData|Tail], NewList) ->
205 NewTdpData = patch(TdpData#'T-BcsmCamelTDPData'{}),
206 patch_tBcsmCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
207
208patch_AnInfoCritList(List) ->
209 % we reverse the origianl list, as the tail recursive _acc function
210 % will invert the order of components again
211 patch_AnInfoCritList_acc(lists:reverse(List), []).
212patch_AnInfoCritList_acc([], NewList) -> NewList;
213patch_AnInfoCritList_acc([Crit|Tail], NewList) ->
214 NewCrit = patch(Crit#'DP-AnalysedInfoCriterium'{}),
215 patch_AnInfoCritList_acc(Tail, [NewCrit|NewList]).
216
217patch_GprsCamelTDPDataList(List) ->
218 % we reverse the origianl list, as the tail recursive _acc function
219 % will invert the order of components again
220 patch_GprsCamelTDPDataList_acc(lists:reverse(List), []).
221patch_GprsCamelTDPDataList_acc([], NewList) -> NewList;
222patch_GprsCamelTDPDataList_acc([TdpData|Tail], NewList) ->
223 NewTdpData = patch(TdpData#'GPRS-CamelTDPData'{}),
224 patch_GprsCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
225
226patch_SmsCamelTDPDataList(List) ->
227 % we reverse the origianl list, as the tail recursive _acc function
228 % will invert the order of components again
229 patch_SmsCamelTDPDataList_acc(lists:reverse(List), []).
230patch_SmsCamelTDPDataList_acc([], NewList) -> NewList;
231patch_SmsCamelTDPDataList_acc([TdpData|Tail], NewList) ->
232 NewTdpData = patch(TdpData#'SMS-CAMEL-TDP-Data'{}),
233 patch_GprsCamelTDPDataList_acc(Tail, [NewTdpData|NewList]).
234
235
236
237% process the Argument of a particular MAP invocation
238process_component_arg(OpCode, Arg) ->
239 case Arg of
240 asn1_NOVALUE -> Arg;
241 _ -> patch(Arg)
242 end.
243
244% recurse over all components
Harald Welte17f64742011-02-10 18:29:59 +0100245handle_tcap_components(asn1_NOVALUE) ->
246 asn1_NOVALUE;
Harald Weltea68d96e2011-02-10 09:49:46 +0100247handle_tcap_components(List) ->
248 % we reverse the origianl list, as the tail recursive _acc function
249 % will invert the order of components again
250 handle_tcap_components_acc(lists:reverse(List), []).
251handle_tcap_components_acc([], NewComponents) -> NewComponents;
252handle_tcap_components_acc([Component|Tail], NewComponents) ->
253 case Component of
254 {basicROS, {Primitive, Body}} ->
255 io:format("handle component ~p primitive ~n", [Component]),
256 case Body of
257 % BEGIN
258 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
259 argument=Arg} ->
260 NewArg = process_component_arg(OpCode, Arg),
261 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100262 #'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100263 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100264 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_begin_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
265 #'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100266 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100267 NewBody = Body#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_begin_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100268 % END
269 #'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
270 argument=Arg} ->
271 NewArg = process_component_arg(OpCode, Arg),
272 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100273 #'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100274 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100275 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
276 #'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100277 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100278 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_end_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100279 % CONTINUE
280 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{opcode={local, OpCode},
281 argument=Arg} ->
282 NewArg = process_component_arg(OpCode, Arg),
283 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_basicROS_invoke'{argument=NewArg};
Harald Welteea193142011-02-10 15:40:36 +0100284 #'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult'{result=#'MapSpecificPDUs_continue_components_SEQOF_basicROS_returnResult_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100285 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100286 NewBody = Body#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult'{result=R#'MapSpecificPDUs_end_components_SEQOF_basicROS_returnResult_result'{result=NewArg}};
287 #'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{opcode={local, OpCode}, result=Arg} = R} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100288 NewArg = process_component_arg(OpCode, Arg),
Harald Welteea193142011-02-10 15:40:36 +0100289 NewBody = Body#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast'{result=R#'MapSpecificPDUs_continue_components_SEQOF_returnResultNotLast_result'{result=NewArg}};
Harald Weltea68d96e2011-02-10 09:49:46 +0100290 _ ->
291 NewBody = Body
292 end,
293 %NewBody = setelement(5, Body, NewArg)
294 NewComponent = {basicROS, {Primitive, NewBody}};
295 _ ->
296 NewComponent = Component
297 end,
298 io:format("=> modified component ~p~n", [NewComponent]),
299 handle_tcap_components_acc(Tail, [NewComponent|NewComponents]).
300
301
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100302% Erlang asn1rt has this strange property that all incoming EXTERNAL types are
303% converted from the 1990 version into the 1994 version. The latter does not
304% preserve the encoding (octet string, single ASN1 type, ...). During encoding,
305% it then uses the OCTTET-STRING encoding, which is different from the MAP
306% customary single-ASN1-type format.
Harald Weltec506fe52011-02-10 13:09:44 +0100307asn1_EXTERNAL1994_fixup({'EXTERNAL', DirRef, IndRef, Data}) when is_list(Data);is_binary(Data) ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100308 % our trick is as follows: we simply convert back to 1990 format, and explicitly
309 % set the single-ASN1-type encoding. asn1rt:s 'enc_EXTERNAL'() will detect this
310 #'EXTERNAL'{'direct-reference' = DirRef, 'indirect-reference' = IndRef,
311 'encoding' = {'single-ASN1-type', Data}};
312asn1_EXTERNAL1994_fixup(Foo) ->
313 Foo.
314
315
316handle_tcap_dialogue(Foo = {'EXTERNAL', DirRef, IndRef, Data}) ->
317 asn1_EXTERNAL1994_fixup(Foo);
318handle_tcap_dialogue(Foo) ->
319 Foo.
320
Harald Weltea68d96e2011-02-10 09:49:46 +0100321
322%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
323% Actual mangling of the decoded MAP messages
324%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
325mangle_map({Type, TcapMsgDec}) ->
326 case {Type, TcapMsgDec} of
327 {'unidirectional', #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dialg,
328 components=Components}} ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100329 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100330 NewComponents = handle_tcap_components(Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100331 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_unidirectional'{dialoguePortion=NewDialg, components=NewComponents};
Harald Welte29c5f402011-02-10 13:24:49 +0100332 {'begin', #'MapSpecificPDUs_begin'{dialoguePortion=Dialg, components=Components}} ->
333 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100334 NewComponents = handle_tcap_components(Components),
Harald Welte29c5f402011-02-10 13:24:49 +0100335 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_begin'{dialoguePortion=NewDialg, components=NewComponents};
Harald Weltea68d96e2011-02-10 09:49:46 +0100336 {'continue', #'MapSpecificPDUs_continue'{dialoguePortion=Dialg, components=Components}} ->
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100337 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100338 NewComponents = handle_tcap_components(Components),
Harald Welte9bc2e4a2011-02-10 12:40:31 +0100339 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_continue'{dialoguePortion=NewDialg, components=NewComponents};
Harald Welte29c5f402011-02-10 13:24:49 +0100340 {'end', #'MapSpecificPDUs_end'{dialoguePortion=Dialg, components=Components}} ->
341 NewDialg = handle_tcap_dialogue(Dialg),
Harald Weltea68d96e2011-02-10 09:49:46 +0100342 NewComponents = handle_tcap_components(Components),
Harald Welte29c5f402011-02-10 13:24:49 +0100343 NewTcapMsgDec = TcapMsgDec#'MapSpecificPDUs_end'{dialoguePortion=NewDialg, components=NewComponents};
344 %{_, #'Abort'{reason=Reason} ->
Harald Weltea68d96e2011-02-10 09:49:46 +0100345 _ ->
346 NewTcapMsgDec = TcapMsgDec
347 end,
Harald Welte29c5f402011-02-10 13:24:49 +0100348 io:format("new TcapMsgDec (Type=~p) ~p~n", [Type, NewTcapMsgDec]),
Harald Weltea68d96e2011-02-10 09:49:46 +0100349 {Type, NewTcapMsgDec}.
350