mgw_nat: explicitly state application name in get/set_env()

This makes sure that even if some function is called from a different
context, it still will use the correct configuration data.
This commit is contained in:
Harald Welte 2012-02-13 22:10:33 +01:00
parent 71d8833bbe
commit a53a63a8da
4 changed files with 29 additions and 29 deletions

View File

@ -36,8 +36,8 @@ patch_map_isdn_addr(From, AddrIn, Type) when is_binary(AddrIn) ->
patch_map_isdn_addr(From, binary_to_list(AddrIn), Type);
patch_map_isdn_addr(From, AddrIn, Type) when is_list(AddrIn) ->
% obtain some configuration data
{ok, Tbl} = application:get_env(map_rewrite_table),
{ok, IntPfx} = application:get_env(intern_pfx),
{ok, Tbl} = application:get_env(mgw_nat, map_rewrite_table),
{ok, IntPfx} = application:get_env(mgw_nat, intern_pfx),
% Decode the list of octets into an party_number
AddrInDec = map_codec:parse_addr_string(AddrIn),
% First we always internationalize the address
@ -71,7 +71,7 @@ patch_map_isdn_digits(From, AddrIn, TypeIn, [Head|Tail]) ->
end.
mangle_msisdn(from_stp, _Opcode, AddrIn) ->
{ok, IntPfx} = application:get_env(intern_pfx),
{ok, IntPfx} = application:get_env(mgw_nat, intern_pfx),
mgw_nat:isup_party_internationalize(AddrIn, IntPfx).
% Someobdy inquires on Routing Info for a MS (from HLR)
@ -135,8 +135,8 @@ patch(From, #'LocationInfoWithLMSI'{'networkNode-Number' = NetNodeNr} = P) ->
patch(_From, {roamingNumber, RoamNumTBCD}) ->
RoamNumIn = map_codec:parse_addr_string(RoamNumTBCD),
io:format("Roaming Number IN = ~p~n", [RoamNumIn]),
{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
{ok, MsrnPfxStp} = application:get_env(mgw_nat, msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(mgw_nat, msrn_pfx_msc),
RoamNumOut = mgw_nat:isup_party_replace_prefix(RoamNumIn, MsrnPfxMsc, MsrnPfxStp),
io:format("Roaming Number OUT = ~p~n", [RoamNumOut]),
RoamNumOutTBCD = map_codec:encode_addr_string(RoamNumOut),
@ -470,9 +470,9 @@ config_update() ->
_ ->
ok
end,
%{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
%{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
%{ok, IntPfx} = application:get_env(intern_pfx),
%{ok, MsrnPfxStp} = application:get_env(mgw_nat, msrn_pfx_stp),
%{ok, MsrnPfxMsc} = application:get_env(mgw_nat, msrn_pfx_msc),
%{ok, IntPfx} = application:get_env(mgw_nat, intern_pfx),
ok.
% Generate the full MAP address rewrite table

View File

@ -168,7 +168,7 @@ do_sccp_gt_rewrite(GT = #global_title{phone_number = PhoneNum}, from_msc, [Head|
% mangle called address
mangle_rx_called(from_stp, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
{ok, RewriteTbl} = application:get_env(mgw_nat, sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, from_stp, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_called(_From, Addr) ->
@ -176,7 +176,7 @@ mangle_rx_called(_From, Addr) ->
% mangle calling address
mangle_rx_calling(from_msc, Addr = #sccp_addr{global_title = GT}) ->
{ok, RewriteTbl} = application:get_env(sccp_rewrite_tbl),
{ok, RewriteTbl} = application:get_env(mgw_nat, sccp_rewrite_tbl),
GTout = do_sccp_gt_rewrite(GT, from_msc, RewriteTbl),
Addr#sccp_addr{global_title = GTout};
mangle_rx_calling(_From, Addr) ->
@ -234,9 +234,9 @@ mangle_isup_number(from_stp, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
case NumType of
?ISUP_PAR_CALLED_P_NUM ->
% First convert to international number, if it is national
{ok, InternPfx} = application:get_env(intern_pfx),
{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
{ok, InternPfx} = application:get_env(mgw_nat, intern_pfx),
{ok, MsrnPfxStp} = application:get_env(mgw_nat, msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(mgw_nat, msrn_pfx_msc),
Num1 = isup_party_internationalize(PartyNum, InternPfx),
io:format("IAM MSRN rewrite (STP->MSC): "),
isup_party_replace_prefix(Num1, MsrnPfxStp, MsrnPfxMsc);
@ -250,9 +250,9 @@ mangle_isup_number(from_msc, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CO
MsgT == ?ISUP_MSGT_ANM ->
case NumType of
?ISUP_PAR_CONNECTED_NUM ->
{ok, InternPfx} = application:get_env(intern_pfx),
{ok, MsrnPfxStp} = application:get_env(msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(msrn_pfx_msc),
{ok, InternPfx} = application:get_env(mgw_nat, intern_pfx),
{ok, MsrnPfxStp} = application:get_env(mgw_nat, msrn_pfx_stp),
{ok, MsrnPfxMsc} = application:get_env(mgw_nat, msrn_pfx_msc),
io:format("CON MSRN rewrite (MSC->STP): "),
Num1 = isup_party_replace_prefix(PartyNum, MsrnPfxStp, MsrnPfxMsc),
% Second: convert to national number, if it is international
@ -264,7 +264,7 @@ mangle_isup_number(from_msc, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CO
mangle_isup_number(from_msc, ?ISUP_MSGT_IAM, NumType, PartyNum) ->
case NumType of
?ISUP_PAR_CALLED_P_NUM ->
{ok, InternPfx} = application:get_env(intern_pfx),
{ok, InternPfx} = application:get_env(mgw_nat, intern_pfx),
isup_party_nationalize(PartyNum, InternPfx);
_ ->
PartyNum
@ -274,7 +274,7 @@ mangle_isup_number(from_stp, MsgT, NumType, PartyNum) when MsgT == ?ISUP_MSGT_CO
MsgT == ?ISUP_MSGT_ANM ->
case NumType of
?ISUP_PAR_CONNECTED_NUM ->
{ok, InternPfx} = application:get_env(intern_pfx),
{ok, InternPfx} = application:get_env(mgw_nat, intern_pfx),
isup_party_internationalize(PartyNum, InternPfx);
_ ->
PartyNum

View File

@ -49,7 +49,7 @@ gen_child_list([Link|Tail], ChildList) ->
gen_child_list(Tail, [NewChild|ChildList]).
get_app_config(Name) ->
case application:get_env(Name) of
case application:get_env(mgw_nat, Name) of
undefined ->
error_logger:error_report([{error, app_cfg_missing},
{get_app_config, Name}]),

View File

@ -33,16 +33,16 @@
% alloc + insert a new masquerade state record in our tables
masq_alloc(DigitsOrig) ->
{ok, Base} = application:get_env(sccp_masq_gt_base),
{ok, Max} = application:get_env(sccp_masq_gt_max),
{ok, Base} = application:get_env(mgw_nat, sccp_masq_gt_base),
{ok, Max} = application:get_env(mgw_nat, sccp_masq_gt_max),
masq_try_alloc(DigitsOrig, Base, Max, 0).
masq_try_alloc(_DigitsOrig, _Base, Max, Offset) when Offset > Max ->
undef;
masq_try_alloc(DigitsOrig, Base, Max, Offset) ->
Try = Base + Offset,
TryBin = osmo_util:int2digit_list(Try),
{ok, RevTbl} = application:get_env(sccp_masq_rev),
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, RevTbl} = application:get_env(mgw_nat, sccp_masq_rev),
{ok, OrigTbl} = application:get_env(mgw_nat, sccp_masq_orig),
% try to first allocate the reverse mapping, i.e. where the new
% masqueraded address is the unique criteria for table lookup
EtsRet = ets:insert_new(RevTbl,
@ -60,7 +60,7 @@ masq_try_alloc(DigitsOrig, Base, Max, Offset) ->
% lookup a masqerade state record
lookup_masq_addr(orig, GtDigits) ->
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, OrigTbl} = application:get_env(mgw_nat, sccp_masq_orig),
case ets:lookup(OrigTbl, GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
@ -69,7 +69,7 @@ lookup_masq_addr(orig, GtDigits) ->
undef
end;
lookup_masq_addr(rev, GtDigits) ->
{ok, RevTbl} = application:get_env(sccp_masq_rev),
{ok, RevTbl} = application:get_env(mgw_nat, sccp_masq_rev),
case ets:lookup(RevTbl, GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
@ -143,14 +143,14 @@ init() ->
reset() ->
io:format("SCCP MASQ: Deleting all MASQ state records~n"),
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, RevTbl} = application:get_env(sccp_masq_rev),
{ok, OrigTbl} = application:get_env(mgw_nat, sccp_masq_orig),
{ok, RevTbl} = application:get_env(mgw_nat, sccp_masq_rev),
ets:delete_all_objects(OrigTbl),
ets:delete_all_objects(RevTbl).
dump() ->
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, RevTbl} = application:get_env(sccp_masq_rev),
{ok, OrigTbl} = application:get_env(mgw_nat, sccp_masq_orig),
{ok, RevTbl} = application:get_env(mgw_nat, sccp_masq_rev),
ListOrig = ets:tab2list(OrigTbl),
ListRev = ets:tab2list(RevTbl),
io:format("SCCP MASQ Table Dump (ORIGINAL)~n"),