Clean-up config options

parent 7b4c5dde
...@@ -33,7 +33,8 @@ ...@@ -33,7 +33,8 @@
-define(SERVER, ?MODULE). -define(SERVER, ?MODULE).
-define(APP, mtproto_proxy). -define(APP, mtproto_proxy).
-define(BURST_MAX, 10). -define(BURST_MAX, 10).
-define(DEFAULT_INIT_CONNS, 4). -define(DEFAULT_INIT_CONNS, 2).
-define(DEFAULT_CLIENTS_PER_CONN, 300).
-type upstream() :: mtp_handler:handle(). -type upstream() :: mtp_handler:handle().
-type downstream() :: mtp_down_conn:handle(). -type downstream() :: mtp_down_conn:handle().
...@@ -224,12 +225,12 @@ maybe_spawn_connection(CurrentMin, #state{pending_downstreams = Pending} = St) - ...@@ -224,12 +225,12 @@ maybe_spawn_connection(CurrentMin, #state{pending_downstreams = Pending} = St) -
%% if N > X and len(pending) < Y -> connect() %% if N > X and len(pending) < Y -> connect()
%% TODO: shrinking (by timer) %% TODO: shrinking (by timer)
ToSpawn = ToSpawn =
case application:get_env(?APP, clients_per_dc_connection) of case application:get_env(?APP, clients_per_dc_connection, ?DEFAULT_CLIENTS_PER_CONN) of
{ok, N} when CurrentMin > N, N when CurrentMin > N,
Pending == [] -> Pending == [] ->
2; 2;
{ok, N} when CurrentMin > (N * 1.5), N when CurrentMin > (N * 1.5),
length(Pending) < ?BURST_MAX -> length(Pending) < ?BURST_MAX ->
%% To survive initial bursts %% To survive initial bursts
?BURST_MAX - length(Pending); ?BURST_MAX - length(Pending);
_ -> _ ->
......
...@@ -36,6 +36,7 @@ ...@@ -36,6 +36,7 @@
-define(HANDSHAKE_TIMEOUT, 8000). -define(HANDSHAKE_TIMEOUT, 8000).
-define(MAX_SOCK_BUF_SIZE, 1024 * 500). % Decrease if CPU is cheaper than RAM -define(MAX_SOCK_BUF_SIZE, 1024 * 500). % Decrease if CPU is cheaper than RAM
-define(MAX_CODEC_BUFFERS, 5 * 1024 * 1024). -define(MAX_CODEC_BUFFERS, 5 * 1024 * 1024).
-define(DEFAULT_CLIENTS_PER_CONN, 300).
-ifndef(OTP_RELEASE). % pre-OTP21 -ifndef(OTP_RELEASE). % pre-OTP21
-define(WITH_STACKTRACE(T, R, S), T:R -> S = erlang:get_stacktrace(), ). -define(WITH_STACKTRACE(T, R, S), T:R -> S = erlang:get_stacktrace(), ).
...@@ -110,7 +111,7 @@ set_config(Conn, Option, Value) -> ...@@ -110,7 +111,7 @@ set_config(Conn, Option, Value) ->
init([Pool, DcId]) -> init([Pool, DcId]) ->
self() ! do_connect, self() ! do_connect,
BpOpts = application:get_env(?APP, downstream_backpressure, #{}), BpOpts = application:get_env(?APP, downstream_backpressure, #{}),
{ok, UpsPerDown} = application:get_env(?APP, clients_per_dc_connection), UpsPerDown = application:get_env(?APP, clients_per_dc_connection, ?DEFAULT_CLIENTS_PER_CONN),
BackpressureConf = build_backpressure_conf(UpsPerDown, BpOpts), BackpressureConf = build_backpressure_conf(UpsPerDown, BpOpts),
{ok, #state{backpressure_conf = BackpressureConf, {ok, #state{backpressure_conf = BackpressureConf,
pool = Pool, pool = Pool,
...@@ -128,7 +129,7 @@ handle_call({set_config, Name, Value}, _From, State) -> ...@@ -128,7 +129,7 @@ handle_call({set_config, Name, Value}, _From, State) ->
ok = inet:setopts(State#state.sock, [{buffer, Value}]), ok = inet:setopts(State#state.sock, [{buffer, Value}]),
{{ok, OldSize}, State}; {{ok, OldSize}, State};
downstream_backpressure when is_map(Value) -> downstream_backpressure when is_map(Value) ->
{ok, UpsPerDown} = application:get_env(?APP, clients_per_dc_connection), UpsPerDown = application:get_env(?APP, clients_per_dc_connection, ?DEFAULT_CLIENTS_PER_CONN),
try build_backpressure_conf(UpsPerDown, Value) of try build_backpressure_conf(UpsPerDown, Value) of
BpConfig -> BpConfig ->
{{ok, State#state.backpressure_conf}, {{ok, State#state.backpressure_conf},
......
...@@ -14,35 +14,13 @@ ...@@ -14,35 +14,13 @@
stdlib stdlib
]}, ]},
{env,[ {env,[
%% Close connection if it failed to perform handshake in this many seconds
{init_timeout_sec, 60},
{hibernate_timeout_sec, 60},
%% Close connection after this many seconds of inactivity
{ready_timeout_sec, 1200},
%% Telegram server uses your external IP address as part of encryption
%% key, so, you should know it.
%% You can configure IP lookup services by `ip_lookup_services' (should
%% return my IP address as one line from this URL) or set IP address
%% statically by `external_ip' (not both).
%% If both are unset, proxy will try to guess IP address
%% from getsockname().
%% `ip_lookup_services' will be tried one-by-one: if 1st is not responding,
%% 2nd one will be tried and so on
{ip_lookup_services,
["http://ipv4.seriyps.ru/",
"http://v4.ident.me/",
"http://ipv4.icanhazip.com/",
"https://digitalresistance.dog/myIp"]},
%% {external_ip, "YOUR.SERVER.EXTERNAL.IP"},
%% Interface to listen for incoming connections %% Interface to listen for incoming connections
%% If not set, 0.0.0.0 will be used %% If not set, 0.0.0.0 will be used (listen on all IPs)
{listen_ip, "0.0.0.0"}, {listen_ip, "0.0.0.0"},
%% You can add as much as you want. Names and ports should be unique %% You can add as much as you want. Names and ports should be unique
{ports, [#{name => mtp_handler_1, {ports, [#{name => mtp_handler_1,
port => 1443, port => 1443,
%% You can tell it to listen on specific IP. %% You can tell each port to listen on specific IP.
%% If not set, top-level listen_ip will be used. %% If not set, top-level listen_ip will be used.
%% listen_ip => "1.2.3.4", %% listen_ip => "1.2.3.4",
...@@ -50,8 +28,12 @@ ...@@ -50,8 +28,12 @@
secret => <<"d0d6e111bada5511fcce9584deadbeef">>, secret => <<"d0d6e111bada5511fcce9584deadbeef">>,
%% tag is what you get from @MTProxybot %% tag is what you get from @MTProxybot
tag => <<"dcbe8f1493fa4cd9ab300891c0b5b326">>}]}, tag => <<"dcbe8f1493fa4cd9ab300891c0b5b326">>}]},
%% number of socket acceptors (per-port)
{num_acceptors, 60}, {num_acceptors, 60},
{max_connections, 40960}, %% maximum number of open connections (per-port)
{max_connections, 64000},
%% It's possible to forbid connection from telegram client to proxy %% It's possible to forbid connection from telegram client to proxy
%% with some of the protocols. Ti's recommended to set this to %% with some of the protocols. Ti's recommended to set this to
%% only `{allowed_protocols, [mtp_secure, mtp_fake_tls]}` because those %% only `{allowed_protocols, [mtp_secure, mtp_fake_tls]}` because those
...@@ -67,8 +49,28 @@ ...@@ -67,8 +49,28 @@
%% {max_connections, [port_name, tls_domain], 15} %% {max_connections, [port_name, tls_domain], 15}
%% ]}, %% ]},
{init_dc_connections, 2}, %% Close connection if it failed to perform handshake in this many seconds
{clients_per_dc_connection, 300}, {init_timeout_sec, 60},
%% Switch client to memory-saving mode after this many seconds of inactivity
{hibernate_timeout_sec, 60},
%% Close client connection after this many seconds of inactivity
{ready_timeout_sec, 1200},
%% Telegram server uses your external IP address as part of encryption
%% key, so, you should know it.
%% You can configure IP lookup services by `ip_lookup_services' (should
%% return my IP address as one line from this URL) or set IP address
%% statically by `external_ip' (not both).
%% If both are unset, proxy will try to guess IP address
%% from getsockname().
%% `ip_lookup_services' will be tried one-by-one: if 1st is not responding,
%% 2nd one will be tried and so on
{ip_lookup_services,
["http://ipv4.seriyps.ru/",
"http://v4.ident.me/",
"http://ipv4.icanhazip.com/",
"https://digitalresistance.dog/myIp"]},
%% {external_ip, "YOUR.SERVER.EXTERNAL.IP"},
%% This option controls how proxy closes client sockets %% This option controls how proxy closes client sockets
%% (SO_LINGER timeout=0 socket option) %% (SO_LINGER timeout=0 socket option)
...@@ -85,6 +87,9 @@ ...@@ -85,6 +87,9 @@
%% - always - always close socket with RST %% - always - always close socket with RST
{reset_close_socket, off}, {reset_close_socket, off},
%% List of enabled replay-attack checks. See
%% https://habr.com/ru/post/452144/
%% server_error_filter - drop server error responses. %% server_error_filter - drop server error responses.
%% Values: %% Values:
%% first - drop server error only if it's 1st server packet %% first - drop server error only if it's 1st server packet
...@@ -93,10 +98,8 @@ ...@@ -93,10 +98,8 @@
%% Default: off %% Default: off
{replay_check_server_error_filter, first}, {replay_check_server_error_filter, first},
%% List of enabled replay-attack checks. See %% Store last used 1st client packets in special storage, drop
%% https://habr.com/ru/post/452144/ %% connections with same 1st packet
%% session_storage - store last used 1st client packets in special
%% storage, drop connections with same 1st packet
%% Values: on/off %% Values: on/off
%% Default: off %% Default: off
{replay_check_session_storage, on}, {replay_check_session_storage, on},
...@@ -139,6 +142,10 @@ ...@@ -139,6 +142,10 @@
%% {total_mem, 3145728} % if connection memory >X - close connection %% {total_mem, 3145728} % if connection memory >X - close connection
%% ]}, %% ]},
%% Multiplexing tuning
%% {init_dc_connections, 2},
%% {clients_per_dc_connection, 300},
%% Downstream backpressure tuning %% Downstream backpressure tuning
%% Values are configured per downstream connection, so, for example, if %% Values are configured per downstream connection, so, for example, if
%% `clients_per_dc_connection' is 300 and current number of connections %% `clients_per_dc_connection' is 300 and current number of connections
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment