[SCCP MASQ] move pool base/max into config file
diff --git a/mgw_nat.app b/mgw_nat.app
index 2172949..6f143f1 100644
--- a/mgw_nat.app
+++ b/mgw_nat.app
@@ -4,12 +4,16 @@
 	 {modules, [mgw_nat_app, mgw_nat_sup, mgw_nat_usr, mgw_nat]},
 	 {mod, {mgw_nat_app, []}},
 	 {env, [
-		% SCCP rewrite
+		% SCCP static rewrite rules
 		{sccp_rewrite_tbl, [
 			{ 12340000, 98760000, "HLR" },
 			{ 12340001, 98760001, "VLR" }
 		]},
 
+		% SCCP source masquerading pool
+		{sccp_masq_gt_base, 12340000},
+		{sccp_masq_gt_max, 9999},
+
 		% ISUP rewrite
 		{msrn_pfx_msc, 35489099},
 		{msrn_pfx_stp, 6392994200},
diff --git a/src/sccp_masq.erl b/src/sccp_masq.erl
index 8cac7b1..f2db5d5 100644
--- a/src/sccp_masq.erl
+++ b/src/sccp_masq.erl
@@ -31,22 +31,21 @@
 	  last_access	% timestamp of last usage
 	}).
 
--define(MASQ_GT_BASE, 12340000).
--define(MASQ_GT_MAX, 9999).
-
 % alloc + insert a new masquerade state record in our tables
 masq_alloc(DigitsOrig) ->
-	masq_try_alloc(DigitsOrig, 0).
-masq_try_alloc(_DigitsOrig, Offset) when Offset > ?MASQ_GT_MAX ->
+	{ok, Base} = application:get_env(sccp_masq_gt_base),
+	{ok, Max} = application:get_env(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, Offset) ->
-	Try = ?MASQ_GT_BASE + Offset,
+masq_try_alloc(DigitsOrig, Base, Max, Offset) ->
+	Try = Base + Offset,
 	EtsRet = ets:insert_new(get(sccp_masq_orig),
 				#sccp_masq_rec{digits_in = DigitsOrig,
 					       digits_out = Try}),
 	case EtsRet of
 		false ->
-			masq_try_alloc(DigitsOrig, Offset+1);
+			masq_try_alloc(DigitsOrig, Base, Max, Offset+1);
 		_ ->
 			ets:insert(get(sccp_masq_rev),
 				   #sccp_masq_rec{digits_in = Try,