erlang
/
osmo-map-masq
Archived
4
0
Fork 0
This repository has been archived on 2022-03-30. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-map-masq/src/tcap_udp_server.erl

121 lines
3.8 KiB
Erlang

-module(tcap_udp_server).
-compile(export_all).
-define(PATCH_HLR_NUMBER, [1]).
-define(PATCH_SGSN_NUMBER, [2]).
-define(PATCH_SGSN_ADDRESS, [3]).
-define(PATCH_VMSC_ADDRESS, [4]).
-include("MAP.hrl").
init(ServerPort) ->
{ok, Sock} = gen_udp:open(ServerPort, [binary, inet]),
loop().
% patch a UpdateGprsLocationArg and replace SGSN number and SGSN address
% !!! TESTING ONLY !!!
patch_UpdateGprsLocationArg(Arg) ->
Arg1 = Arg#'UpdateGprsLocationArg'{'sgsn-Number' = ?PATCH_SGSN_NUMBER},
Arg1#'UpdateGprsLocationArg'{'sgsn-Address' = ?PATCH_SGSN_ADDRESS}.
% Some other SGSN is sendingu us a GPRS location update. In the response,
% we indicate teh HLR number, which we need to masquerade
patch_UpdateGprsLocationRes(Arg) ->
Arg#'UpdateGprsLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER}.
% Some other MSC/VLR is sendingu us a GSM location update. In the response,
% we indicate teh HLR number, which we need to masquerade
patch_UpdateLocationRes(Arg) ->
Arg#'UpdateLocationRes'{'hlr-Number' = ?PATCH_HLR_NUMBER}.
% HLR responds to VLR's MAP_RESTORE_REQ (i.e. it has lost information)
patch_RestoreDataRes(Arg) ->
Arg#'RestoreDataRes'{'hlr-Number' = ?PATCH_HLR_NUMBER}.
% HLR sends subscriber data to VLR/SGSN, including CAMEL info
patch_InsertSubscriberDataArg(Arg) ->
VlrCamel = Arg#'InsertSubscriberDataArg'.'vlrCamelSubscriptionInfo',
%Arg1 = Arg#'InsertSubscriberDataArg'{'vlrCamelSubscriptionInfo' = patch_vlrCamelSubscrInfo(VlrCamel)},
SgsnCamel = Arg#'InsertSubscriberDataArg'.'sgsn-CAMEL-SubscriptionInfo',
%Arg#'InsertSubscriberDataArg'{'sgsn-CAMEL-SubscriptionInfo' = patch_sgsnCamelSubscrInfo(SgsnCamel)},
Arg.
%patch_vlrCamelSubscrInfo(VlrCamel) ->
% case VlrCamel of
% asn1_NOVALUE ->
% VlrCamel;
% {'CAMEL-SubscriptionInfo', {Sinfo}} ->
% Sinfo#
%patch_sgsnCamelSubscrInfo(SgsnCamel) ->
% case SgsnCamel of
% asn1_NOVALUE ->
% SgsnCamel;
% {'SGSN-CAMEL-SubscriptionInfo', {Sinfo}} ->
% Gcsi = Sinfo#'SGSN-CAMEL-SubscriptionInfo'.'gprs=CSI',
% case Gcsi of
% asn1_NOVALUE ->
% SgsnCamel;
% {'GPRS-CSI', {Gcsi}} ->
% TdpList =
% process the Argument of a particular MAP invocation
process_component_arg(OpCode, Arg) ->
case Arg of
asn1_NOVALUE -> Arg;
_ -> patch_UpdateGprsLocationArg(Arg)
end.
% recurse over all components
handle_tcap_components([]) -> 0;
handle_tcap_components([Component|Tail]) ->
case Component of
{basicROS, {Primitive, Body}} ->
io:format("handle component ~p primitive ~n", [Component]),
case Body of
{'MapSpecificPDUs_begin_components_SEQOF_basicROS_invoke', _, _, {local, OpCode}, Arg} ->
NewArg = process_component_arg(OpCode, Arg),
end,
NewBody = setelement(5, Body, NewArg)
end,
NewComponent = {basicROS, {Primitive, NewBody}},
io:format("=> modified component ~p~n", [NewComponent]),
handle_tcap_components(Tail).
handle_tcap_msg_dec(TcapMsgDec) ->
case TcapMsgDec of
{'unidirectional', {'MapSpecificPDUs_unidirectional', Dialg, Components}} ->
NewComponents = handle_tcap_components(Components);
{'begin', {'MapSpecificPDUs_begin', Otid, Dialg, Components}} ->
NewComponents = handle_tcap_components(Components);
{'continue', {'MapSpecificPDUs_continue', Otid, Dtid, Dialg, Components}} ->
NewComponents = handle_tcap_components(Components);
{'end', {'MapSpecificPDUs_end', Dtid, Dialg, Components}} ->
NewComponents = handle_tcap_components(Components)
end.
handle_tcap_msg(PayloadL) ->
io:format("aboout to tcap_msg_dec..."),
case asn1rt:decode('MAP', 'MapSpecificPDUs', PayloadL) of
{ok, TcapMsgDec} ->
io:format("success!~n"),
handle_tcap_msg_dec(TcapMsgDec);
Error -> Error
end.
loop() ->
io:format("udp_server_loop~n"),
receive {udp, Sock, ClientIP, ClientPort, Packet} ->
io:format("UDP received from ~p:~p ==> ~p~n", [ClientIP, ClientPort, Packet]),
handle_tcap_msg(binary_to_list(Packet))%,
%loop()
end.