make sure sccp_masq is using the application environment for ets

This commit is contained in:
Harald Welte 2011-09-24 12:07:44 +02:00
parent 26647e0f4f
commit 392ce05473
1 changed files with 18 additions and 10 deletions

View File

@ -41,16 +41,18 @@ masq_try_alloc(_DigitsOrig, _Base, Max, Offset) when Offset > Max ->
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),
% 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(get(sccp_masq_rev),
EtsRet = ets:insert_new(RevTbl,
#sccp_masq_rec{digits_in = TryBin,
digits_out = DigitsOrig}),
case EtsRet of
false ->
masq_try_alloc(DigitsOrig, Base, Max, Offset+1);
_ ->
ets:insert(get(sccp_masq_orig),
ets:insert(OrigTbl,
#sccp_masq_rec{digits_in = DigitsOrig,
digits_out = TryBin}),
Try
@ -58,7 +60,8 @@ masq_try_alloc(DigitsOrig, Base, Max, Offset) ->
% lookup a masqerade state record
lookup_masq_addr(orig, GtDigits) ->
case ets:lookup(get(sccp_masq_orig), GtDigits) of
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
case ets:lookup(OrigTbl, GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
_ ->
@ -66,7 +69,8 @@ lookup_masq_addr(orig, GtDigits) ->
undef
end;
lookup_masq_addr(rev, GtDigits) ->
case ets:lookup(get(sccp_masq_rev), GtDigits) of
{ok, RevTbl} = application:get_env(sccp_masq_rev),
case ets:lookup(RevTbl, GtDigits) of
[#sccp_masq_rec{digits_out = DigitsOut}] ->
DigitsOut;
_ ->
@ -133,18 +137,22 @@ init() ->
{keypos, #sccp_masq_rec.digits_in}]),
Rev = ets:new(sccp_masq_rev, [ordered_set,
{keypos, #sccp_masq_rec.digits_in}]),
put(sccp_masq_orig, Orig),
put(sccp_masq_rev, Rev),
application:set_env(mgw_nat, sccp_masq_orig, Orig),
application:set_env(mgw_nat, sccp_masq_rev, Rev),
ok.
reset() ->
io:format("SCCP MASQ: Deleting all MASQ state records~n"),
ets:delete_all_objects(get(sccp_masq_orig)),
ets:delete_all_objects(get(sccp_masq_rev)).
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, RevTbl} = application:get_env(sccp_masq_rev),
ets:delete_all_objects(OrigTbl),
ets:delete_all_objects(RevTbl).
dump() ->
ListOrig = ets:tab2list(get(sccp_masq_orig)),
ListRev = ets:tab2list(get(sccp_masq_rev)),
{ok, OrigTbl} = application:get_env(sccp_masq_orig),
{ok, RevTbl} = application:get_env(sccp_masq_rev),
ListOrig = ets:tab2list(OrigTbl),
ListRev = ets:tab2list(RevTbl),
io:format("SCCP MASQ Table Dump (ORIGINAL)~n"),
dump_list(ListOrig),
io:format("SCCP MASQ Table Dump (REVERSE)~n"),