Secret and tag now have to be put into config in hex

parent a31589f4
...@@ -3,6 +3,8 @@ Erlang mtproto proxy ...@@ -3,6 +3,8 @@ Erlang mtproto proxy
This part of code was extracted from [@socksy_bot](https://t.me/socksy_bot). This part of code was extracted from [@socksy_bot](https://t.me/socksy_bot).
This implementation supports promoted channels! See `mtproto_proxy_app.src` `tag` option.
How to start How to start
------------ ------------
...@@ -49,6 +51,7 @@ See `src/mtproto_proxy.app.src`. ...@@ -49,6 +51,7 @@ See `src/mtproto_proxy.app.src`.
Secret key will be printed on start. Secret key will be printed on start.
Helpers Helpers
------- -------
......
...@@ -11,7 +11,7 @@ ...@@ -11,7 +11,7 @@
%% API %% API
-export([start_link/4]). -export([start_link/4]).
-export([hex/1]). -export([hex/1, unhex/1]).
-export([keys_str/0]). -export([keys_str/0]).
%% Callbacks %% Callbacks
...@@ -103,8 +103,8 @@ init({_Ref, Socket, Transport, [Secret, Tag]}) -> ...@@ -103,8 +103,8 @@ init({_Ref, Socket, Transport, [Secret, Tag]}) ->
Timer = gen_timeout:new( Timer = gen_timeout:new(
#{timeout => {env, ?APP, TimeoutKey, TimeoutDefault}}), #{timeout => {env, ?APP, TimeoutKey, TimeoutDefault}}),
State = #state{up_sock = Socket, State = #state{up_sock = Socket,
secret = Secret, secret = unhex(Secret),
proxy_tag = Tag, proxy_tag = unhex(Tag),
up_transport = Transport, up_transport = Transport,
started_at = erlang:system_time(second), started_at = erlang:system_time(second),
timer = Timer}, timer = Timer},
...@@ -486,6 +486,13 @@ hex(Bin) -> ...@@ -486,6 +486,13 @@ hex(Bin) ->
end end
end || <<N:4>> <= Bin>>. end || <<N:4>> <= Bin>>.
unhex(Chars) ->
UnHChar = fun(C) when C < $W -> C - $0;
(C) when C > $W -> C - $W
end,
<< <<(UnHChar(C)):4>> || <<C>> <= Chars>>.
track(Direction, Data) -> track(Direction, Data) ->
Size = byte_size(Data), Size = byte_size(Data),
metric:count_inc([?APP, tracker, bytes], Size, #{labels => [Direction]}), metric:count_inc([?APP, tracker, bytes], Size, #{labels => [Direction]}),
......
...@@ -19,8 +19,8 @@ ...@@ -19,8 +19,8 @@
%% {external_ip, "YOUR.SERVER.EXTERNAL.IP"}, %% {external_ip, "YOUR.SERVER.EXTERNAL.IP"},
{ports, [#{name => mtp_handler, {ports, [#{name => mtp_handler,
port => 1443, port => 1443,
secret => <<208,214,225,17,186,218,85,17,252,206,149,132,222,173,190,239>>, secret => <<"d0d6e111bada5511fcce9584deadbeef">>,
tag => <<220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38>>}]}, tag => <<"dcbe8f1493fa4cd9ab300891c0b5b326">>}]},
{num_acceptors, 60}, {num_acceptors, 60},
{max_connections, 20480} {max_connections, 20480}
]}, ]},
......
...@@ -42,8 +42,8 @@ start_proxy(#{name := Name, port := Port, secret := Secret, tag := Tag}) -> ...@@ -42,8 +42,8 @@ start_proxy(#{name := Name, port := Port, secret := Secret, tag := Tag}) ->
{num_acceptors, NumAcceptors}, {num_acceptors, NumAcceptors},
{max_connections, MaxConnections}], {max_connections, MaxConnections}],
mtp_handler, [Secret, Tag]), mtp_handler, [Secret, Tag]),
io:format("Proxy started on ~s:~p with key: ~s~n", io:format("Proxy started on ~s:~p with secret: ~s~n",
[inet:ntoa(ListenIp), Port, mtp_handler:hex(Secret)]), [inet:ntoa(ListenIp), Port, Secret]),
Res. Res.
stop_proxy(#{name := Name}) -> stop_proxy(#{name := Name}) ->
......
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