Implement sponsored channels and work through official endpoints

parent 8b2e3906
...@@ -3,7 +3,7 @@ ...@@ -3,7 +3,7 @@
{parse_transform, lager_transform}]}. {parse_transform, lager_transform}]}.
{deps, [{ranch, "1.5.0"}, {deps, [{ranch, "1.5.0"},
{lager, "3.6.1"} {lager, "3.6.3"}
]}. ]}.
{relx, [{release, { mtp_proxy, "0.1.0" }, {relx, [{release, { mtp_proxy, "0.1.0" },
......
{"1.1.0", {"1.1.0",
[{<<"goldrush">>,{pkg,<<"goldrush">>,<<"0.1.9">>},1}, [{<<"goldrush">>,{pkg,<<"goldrush">>,<<"0.1.9">>},1},
{<<"lager">>,{pkg,<<"lager">>,<<"3.6.1">>},0}, {<<"lager">>,{pkg,<<"lager">>,<<"3.6.3">>},0},
{<<"ranch">>,{pkg,<<"ranch">>,<<"1.5.0">>},0}]}. {<<"ranch">>,{pkg,<<"ranch">>,<<"1.5.0">>},0}]}.
[ [
{pkg_hash,[ {pkg_hash,[
{<<"goldrush">>, <<"F06E5D5F1277DA5C413E84D5A2924174182FB108DABB39D5EC548B27424CD106">>}, {<<"goldrush">>, <<"F06E5D5F1277DA5C413E84D5A2924174182FB108DABB39D5EC548B27424CD106">>},
{<<"lager">>, <<"9D29C5FF7F926D25ECD9899990867C9152DCF34EEE65BAC8EC0DFC0D16A26E0C">>}, {<<"lager">>, <<"FE78951D174616273F87F0DBC3374D1430B1952E5EFC4E1C995592D30A207294">>},
{<<"ranch">>, <<"F04166F456790FEE2AC1AA05A02745CC75783C2BFB26D39FAF6AEFC9A3D3A58A">>}]} {<<"ranch">>, <<"F04166F456790FEE2AC1AA05A02745CC75783C2BFB26D39FAF6AEFC9A3D3A58A">>}]}
]. ].
%%% @author sergey <me@seriyps.ru>
%%% @copyright (C) 2018, sergey
%%% @doc
%%% Interface for logging metrics (CODE WIPED)
%%% @end
%%% Created : 15 May 2018 by sergey <me@seriyps.ru>
-module(metric).
-export([count_inc/3,
gauge_set/3,
rt/2,
histogram_observe/3]).
count_inc(_Name, _Value, _Extra) ->
noop.
gauge_set(_Name, _Value, _Extra) ->
noop.
histogram_observe(_Name, _Value, _Extra) ->
noop.
rt(_Name, _Fun) ->
noop.
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% MTProto abridged packet format codec
%%% @end
%%% Created : 29 May 2018 by Sergey <me@seriyps.ru>
-module(mtp_abridged).
-behaviour(mtp_layer).
-export([new/0,
try_decode_packet/2,
encode_packet/2]).
-export_type([codec/0]).
-record(st,
{buffer = <<>> :: binary()}).
-define(MAX_PACKET_SIZE, 1 * 1024 * 1024). % 1mb
-define(APP, mtproto_proxy).
-opaque codec() :: #st{}.
new() ->
#st{}.
-spec try_decode_packet(binary(), codec()) -> {ok, binary(), codec()}
| {incomplete, codec()}.
try_decode_packet(<<Flag, Len:24/unsigned-little-integer, Rest/binary>> = Data,
#st{buffer = <<>>} = St) when Flag == 127; Flag == 255 ->
Len1 = Len * 4,
(Len1 < ?MAX_PACKET_SIZE)
orelse
begin
metric:count_inc([?APP, protocol_error, total], 1, #{labels => [abriged_max_size]}),
error({packet_too_large, Len1})
end,
try_decode_packet_len(Len1, Rest, Data, St);
try_decode_packet(<<Len, Rest/binary>> = Data,
#st{buffer = <<>>} = St) when Len >= 128 ->
Len1 = (Len - 128) * 4,
try_decode_packet_len(Len1, Rest, Data, St);
try_decode_packet(<<Len, Rest/binary>> = Data,
#st{buffer = <<>>} = St) when Len < 127 ->
Len1 = Len * 4,
try_decode_packet_len(Len1, Rest, Data, St);
try_decode_packet(Bin, #st{buffer = Buf} = St) when byte_size(Buf) > 0 ->
try_decode_packet(<<Buf/binary, Bin/binary>>, St#st{buffer = <<>>});
try_decode_packet(Bin, #st{buffer = <<>>} = St) ->
{incomplete, St#st{buffer = Bin}}.
try_decode_packet_len(Len, LenStripped, Data, St) ->
case LenStripped of
<<Packet:Len/binary, Rest/binary>> ->
{ok, Packet, St#st{buffer = Rest}};
_ ->
{incomplete, St#st{buffer = Data}}
end.
-spec encode_packet(binary(), codec()) -> iodata().
encode_packet(Bin, St) ->
Size = byte_size(Bin),
Len = Size div 4,
Packet =
case Len < 127 of
true ->
[Len | Bin];
false ->
[<<127, Len:24/unsigned-little-integer>> | Bin]
end,
{Packet, St}.
-ifdef(TEST).
-include_lib("eunit/include/eunit.hrl").
decode_none_test() ->
S = new(),
?assertEqual(
{incomplete, S}, try_decode_packet(<<>>, S)).
-endif.
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% Block CBC AES codec with buffered decoding
%%% @end
%%% Created : 6 Jun 2018 by Sergey <me@seriyps.ru>
-module(mtp_aes_cbc).
-behaviour(mtp_layer).
-export([new/5,
encrypt/2,
decrypt/2,
try_decode_packet/2,
encode_packet/2
]).
-export_type([codec/0]).
-record(baes_st,
{decode_buf :: binary(),
block_size :: pos_integer(),
encrypt :: any(), % aes state
decrypt :: any() % aes state
}).
-opaque codec() :: #baes_st{}.
new(EncKey, EncIv, DecKey, DecIv, BlockSize) ->
#baes_st{
decode_buf = <<>>,
block_size = BlockSize,
encrypt = {EncKey, EncIv},
decrypt = {DecKey, DecIv}
}.
-spec encrypt(iodata(), codec()) -> {binary(), codec()}.
encrypt(Data, #baes_st{block_size = BSize,
encrypt = {EncKey, EncIv}} = S) ->
((iolist_size(Data) rem BSize) == 0)
orelse error({data_not_aligned, BSize, byte_size(Data)}),
Encrypted = crypto:block_encrypt(aes_cbc, EncKey, EncIv, Data),
{Encrypted, S#baes_st{encrypt = {EncKey, crypto:next_iv(aes_cbc, Encrypted)}}}.
-spec decrypt(binary(), codec()) -> {binary(), codec()}.
decrypt(Data, #baes_st{block_size = BSize,
decode_buf = <<>>} = S) ->
Size = byte_size(Data),
Div = Size div BSize,
Rem = Size rem BSize,
case {Div, Rem} of
{0, _} ->
%% Not enough bytes
{<<>>, S#baes_st{decode_buf = Data}};
{_, 0} ->
%% Aligned
do_decrypt(Data, S);
{_, Tail} ->
%% N blocks + reminder
Head = Size - Tail,
<<ToDecode:Head/binary, Reminder/binary>> = Data,
do_decrypt(ToDecode, S#baes_st{decode_buf = Reminder})
end;
decrypt(Data, #baes_st{decode_buf = Buf} = S) ->
decrypt(<<Buf/binary, Data/binary>>, S#baes_st{decode_buf = <<>>}).
do_decrypt(Data, #baes_st{decrypt = {DecKey, DecIv}} = S) ->
Decrypted = crypto:block_decrypt(aes_cbc, DecKey, DecIv, Data),
NewDecIv = crypto:next_iv(aes_cbc, Data),
{Decrypted, S#baes_st{decrypt = {DecKey, NewDecIv}}}.
%% To comply mtp_layer interface
try_decode_packet(Bin, S) ->
case decrypt(Bin, S) of
{<<>>, S1} ->
{incomplete, S1};
{Dec, S1} ->
{ok, Dec, S1}
end.
encode_packet(Bin, S) ->
encrypt(Bin, S).
-ifdef(TEST).
-include_lib("eunit/include/eunit.hrl").
decode_none_test() ->
DecKey = <<21,211,191,127,143,222,184,152,232,213,25,173,243,163,243,224,133,131,199,13,206,156,146,141,67,172,85,114,190,203,176,215>>,
DecIV = <<9,156,175,247,37,161,219,155,52,115,93,76,122,195,158,194>>,
S = new(DecKey, DecIV, DecKey, DecIV, 16),
?assertEqual(
{incomplete, S}, try_decode_packet(<<>>, S)).
decrypt_test() ->
DecKey = <<21,211,191,127,143,222,184,152,232,213,25,173,243,163,243,224,133,131,199,13,206,156,146,141,67,172,85,114,190,203,176,215>>,
DecIV = <<9,156,175,247,37,161,219,155,52,115,93,76,122,195,158,194>>,
S = new(DecKey, DecIV, DecKey, DecIV, 16),
Samples =
[{<<36,170,147,95,53,27,44,255,252,105,70,8,90,40,77,226>>,
<<44,0,0,0,255,255,255,255,245,238,130,118,0,0,0,0>>},
{<<137,187,80,238,110,142,52,130,119,140,210,138,13,72,169,144,63,167,172,19,161,13,231,169,237,34,203,240,8,135,67,29>>,
<<134,153,66,10,95,9,134,49,221,133,21,91,73,80,73,80,80,82,80,68,84,73,77,69,133,250,76,84,4,0,0,0>>}
],
lists:foldl(
fun({In, Out}, S1) ->
{Dec, S2} = decrypt(In, S1),
?assertEqual(Out, Dec),
S2
end, S, Samples).
encrypt_test() ->
EncKey = <<89,84,72,247,172,56,204,11,10,242,143,240,111,53,33,162,221,141,148,243,100,21,167,160,132,99,61,189,128,73,138,89>>,
EncIV = <<248,195,42,53,235,104,78,225,84,171,182,125,18,192,251,77>>,
S = new(EncKey, EncIV, EncKey, EncIV, 16),
Samples =
[{<<44,0,0,0,255,255,255,255,245,238,130,118,0,0,0,0,73,80,73,80,80,82,80,68,84,73,77,69,73,80,73,80,80,82,80,68,84,73,77,69,2,118,29,129,4,0,0,0>>,
<<161,206,198,191,175,240,48,162,245,192,234,210,104,195,161,214,55,147,145,157,174,33,243,198,84,188,29,201,116,128,185,149,73,241,149,122,244,193,59,112,153,188,141,134,90,24,75,216>>},
{<<136,0,0,0,0,0,0,0,238,241,206,54,8,16,2,64,195,43,106,127,211,218,156,102,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,65,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,66,24,0,0,0,174,38,30,219,16,220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,56,220,23,91,20,0,0,0,120,151,70,96,26,49,96,74,221,243,104,13,173,13,132,192,238,22,97,126,247,233,151,22,4,0,0,0,4,0,0,0>>,
<<92,173,139,247,1,147,48,108,162,98,125,215,170,185,87,131,65,26,90,205,43,54,115,216,90,101,3,188,151,165,126,144,104,247,57,65,32,107,245,154,77,194,161,157,63,232,169,68,113,64,96,197,10,209,66,117,251,15,10,141,248,122,40,242,195,38,196,237,68,132,189,49,102,53,31,139,56,64,213,107,79,105,210,182,157,73,203,105,165,134,163,116,49,94,143,171,88,132,84,123,196,38,35,53,220,182,232,199,92,29,182,129,239,116,252,31,72,29,120,203,57,49,46,129,142,94,204,121,21,113,211,10,193,126,180,227,139,40,85,223,134,124,152,81>>}],
lists:foldl(
fun({In, Out}, S1) ->
{Enc, S2} = encrypt(In, S1),
?assertEqual(Out, Enc),
S2
end, S, Samples).
-endif.
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% MTProto "full" packet format with padding
%%% ```
%%% <<MsgLen:32/integer, SeqNo:32/integer, Body:MsgLen/binary, CRC:32/integer>>
%%% ```
%%% @end
%%% Created : 6 Jun 2018 by Sergey <me@seriyps.ru>
-module(mtp_full).
-behaviour(mtp_layer).
-export([new/0, new/2,
try_decode_packet/2,
encode_packet/2]).
-export_type([codec/0]).
-record(full_st,
{decode_buf = <<>> :: binary(),
enc_seq_no :: integer(),
dec_seq_no :: integer()}).
-define(MIN_MSG_LEN, 12).
-define(MAX_MSG_LEN, 16777216). %2^24 - 16mb
-define(BLOCK_SIZE, 16).
-define(PAD, <<4:32/little>>).
-define(APP, mtproto_proxy).
-opaque codec() :: #full_st{}.
new() ->
new(0, 0).
new(EncSeqNo, DecSeqNo) ->
#full_st{enc_seq_no = EncSeqNo,
dec_seq_no = DecSeqNo}.
try_decode_packet(<<4:32/little, Bin/binary>>, #full_st{decode_buf = <<>>} = S) ->
%% Skip padding
try_decode_packet(Bin, S);
try_decode_packet(<<Len:32/little, PktSeqNo:32/signed-little, Tail/binary>> = Bin,
#full_st{decode_buf = <<>>, dec_seq_no = SeqNo} = S) ->
((Len rem byte_size(?PAD)) == 0)
orelse error({wrong_alignement, Len}),
((?MIN_MSG_LEN =< Len) and (Len =< ?MAX_MSG_LEN))
orelse error({wrong_msg_len, Len}),
(SeqNo == PktSeqNo)
orelse error({wrong_seq_no, SeqNo, PktSeqNo}),
BodyLen = Len - 4 - 4 - 4,
case Tail of
<<Body:BodyLen/binary, CRC:32/little, Rest/binary>> ->
PacketCrc = erlang:crc32([<<Len:32/little, PktSeqNo:32/little>> | Body]),
(CRC == PacketCrc)
orelse error({wrong_checksum, CRC, PacketCrc}),
{ok, Body, S#full_st{decode_buf = Rest, dec_seq_no = SeqNo + 1}};
_ ->
{incomplete, S#full_st{decode_buf = Bin}}
end;
try_decode_packet(Bin, #full_st{decode_buf = Buf} = S) when byte_size(Buf) > 0 ->
try_decode_packet(<<Buf/binary, Bin/binary>>, S#full_st{decode_buf = <<>>});
try_decode_packet(Bin, #full_st{decode_buf = <<>>} = S) ->
{incomplete, S#full_st{decode_buf = Bin}}.
encode_packet(Bin, #full_st{enc_seq_no = SeqNo} = S) ->
BodySize = iolist_size(Bin),
((BodySize rem byte_size(?PAD)) == 0)
orelse error({wrong_alignment, BodySize}),
Len = BodySize + 4 + 4 + 4,
MsgNoChecksum =
[<<Len:32/unsigned-little-integer,
SeqNo:32/signed-little-integer>>
| Bin],
CheckSum = erlang:crc32(MsgNoChecksum),
FullMsg = [MsgNoChecksum | <<CheckSum:32/unsigned-little-integer>>],
Len = iolist_size(FullMsg),
%% XXX: is there a cleaner way?
PaddingSize = (?BLOCK_SIZE - (Len rem ?BLOCK_SIZE)) rem ?BLOCK_SIZE,
NPaddings = PaddingSize div byte_size(?PAD),
Padding = lists:duplicate(NPaddings, ?PAD),
{[FullMsg | Padding], S#full_st{enc_seq_no = SeqNo + 1}}.
-ifdef(TEST).
-include_lib("eunit/include/eunit.hrl").
encode_nopadding_test() ->
S = new(),
{Enc, _S1} = encode_packet(<<1, 1, 1, 1>>, S),
?assertEqual(
<<16,0,0,0,
0,0,0,0,
1,1,1,1,
22,39,175,160>>,
iolist_to_binary(Enc)).
encode_padding_test() ->
S = new(),
{Enc, _S1} = encode_packet(<<1,1,1,1,1,1,1,1>>, S),
?assertEqual(
<<20,0,0,0,0,0,0,0, %size, seq no
1,1,1,1,1,1,1,1, %data
246,196,46,149, %CRC
4,0,0,0,4,0,0,0,4,0,0,0>>, %padding
iolist_to_binary(Enc)).
encode_padding_seq_test() ->
S = new(),
{Enc1, S1} = encode_packet(binary:copy(<<9>>, 8), S),
?assertEqual(
<<20,0,0,0,
0,0,0,0,
9,9,9,9,9,9,9,9,
229,35,162,164,
4, 0,0,0,4,0,0,0,4,0,0,0>>,
iolist_to_binary(Enc1)),
{Enc2, _S2} = encode_packet(binary:copy(<<8>>, 8), S1),
?assertEqual(
<<20,0,0,0,
1,0,0,0,
8,8,8,8,8,8,8,8,
48,146,132,116,
4,0,0,0,4,0,0,0,4,0,0,0>>,
iolist_to_binary(Enc2)).
decode_none_test() ->
S = new(),
?assertEqual(
{incomplete, S}, try_decode_packet(<<>>, S)).
codec_test() ->
S = new(),
Packets = [
binary:copy(<<0>>, 4), %non-padded
binary:copy(<<1>>, 8), %padded
binary:copy(<<2>>, 4), %non-padded
binary:copy(<<2>>, 100) %padded
],
lists:foldl(
fun(B, S1) ->
{Encoded, S2} = encode_packet(B, S1),
BinEncoded = iolist_to_binary(Encoded),
{ok, Decoded, S3} = try_decode_packet(BinEncoded, S2),
?assertEqual(B, Decoded, {BinEncoded, S2, S3}),
S3
end, S, Packets).
codec_stream_test() ->
S = new(),
Packets = [
binary:copy(<<0>>, 4), %non-padded
binary:copy(<<1>>, 8), %padded
binary:copy(<<2>>, 4), %non-padded
binary:copy(<<2>>, 100) %padded
],
{Encoded, SS} =
lists:foldl(
fun(B, {Enc1, S1}) ->
{Enc2, S2} = encode_packet(B, S1),
{[Enc1 | Enc2], S2}
end, {[], S}, Packets),
lists:foldl(
fun(B, {Enc, S1}) ->
{ok, Dec, S2} = try_decode_packet(Enc, S1),
?assertEqual(B, Dec),
{<<>>, S2}
end, {iolist_to_binary(Encoded), SS}, Packets).
-endif.
This diff is collapsed.
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% Behaviour for MTProto layer codec
%%% @end
%%% Created : 6 Jun 2018 by Sergey <me@seriyps.ru>
-module(mtp_layer).
-export([new/2,
try_decode_packet/2,
encode_packet/2]).
-export([fold_packets/4]).
-export_type([codec/0,
layer/0]).
-type state() :: any().
-type codec() :: mtb_aes_cbc
| mtp_abridged
| mtp_full
| mtp_obfuscated
| mtp_rpc
| mtp_wrap.
-type layer() :: {codec(), state()} | ident.
-callback try_decode_packet(binary(), state()) ->
{ok, binary(), state()}
| {incomplete, state()}.
-callback encode_packet(binary(), state()) ->
{binary(), state()}.
new(Mod, S) ->
{Mod, S}.
encode_packet(Msg, ident) ->
{Msg, ident};
encode_packet(Msg, {Mod, St}) ->
{Enc, St1} = Mod:encode_packet(Msg, St),
{Enc, {Mod, St1}}.
try_decode_packet(Msg, ident) ->
{ok, Msg, ident};
try_decode_packet(Msg, {Mod, St}) ->
case Mod:try_decode_packet(Msg, St) of
{ok, Dec, St1} ->
{ok, Dec, {Mod, St1}};
{incomplete, St1} ->
{incomplete, {Mod, St1}}
end.
-spec fold_packets(fun( (binary(), FoldSt) -> FoldSt ),
FoldSt, binary(), layer()) ->
{ok, FoldSt, layer()}
when
FoldSt :: any().
fold_packets(Fun, FoldSt, Data, ident) ->
FoldSt1 = Fun(Data, FoldSt),
{ok, FoldSt1, ident};
fold_packets(Fun, FoldSt, Data, Layer) ->
case try_decode_packet(Data, Layer) of
{ok, Decoded, L1} ->
FoldSt1 = Fun(Decoded, FoldSt),
fold_packets(Fun, FoldSt1, <<>>, L1);
{incomplete, L1} ->
{ok, FoldSt, L1}
end.
...@@ -6,11 +6,17 @@ ...@@ -6,11 +6,17 @@
%%% Created : 29 May 2018 by Sergey <me@seriyps.ru> %%% Created : 29 May 2018 by Sergey <me@seriyps.ru>
-module(mtp_obfuscated). -module(mtp_obfuscated).
-export([new/0, -behaviour(mtp_layer).
new/1, -export([create/0,
create/1,
from_header/2, from_header/2,
new/4,
encrypt/2, encrypt/2,
decrypt/2]). decrypt/2,
try_decode_packet/2,
encode_packet/2
]).
-export([bin_rev/1]).
-export_type([codec/0]). -export_type([codec/0]).
...@@ -19,36 +25,26 @@ ...@@ -19,36 +25,26 @@
decrypt :: any() % aes state decrypt :: any() % aes state
}). }).
-define(ENDPOINTS, {
{149, 154, 175, 50},
{149, 154, 167, 51},
{149, 154, 175, 100},
{149, 154, 167, 91},
{149, 154, 171, 5}
}).
-define(APP, mtproto_proxy). -define(APP, mtproto_proxy).
%% -define(DBG(Fmt, Args), io:format(user, Fmt, Args)).
-define(DBG(_F, _A), ok).
-opaque codec() :: #st{}. -opaque codec() :: #st{}.
%% @doc Creates new obfuscated stream (usual format) %% @doc Creates new obfuscated stream (usual format)
-spec new() -> {ok, Header :: binary(), codec()}. -spec create() -> {ok, Header :: binary(), codec()}.
new() -> create() ->
new(crypto:strong_rand_bytes(60)). create(crypto:strong_rand_bytes(60)).
-spec new(binary()) -> {ok, Header :: binary(), codec()}. -spec create(binary()) -> {ok, Header :: binary(), codec()}.
new(<<Left:56/binary, Right:4/binary>>) -> create(<<Left:56/binary, Right:4/binary>>) ->
DownHeader = <<Left/binary, DownHeader = <<Left/binary,
16#ef, 16#ef, 16#ef, 16#ef, 16#ef, 16#ef, 16#ef, 16#ef,
Right/binary>>, Right/binary>>,
new2(DownHeader). new2(DownHeader).
new2(<<Left:56/binary, _/binary>> = DownHeader) -> new2(<<Left:56/binary, _/binary>> = DownHeader) ->
Encrypt = init_down_encrypt(DownHeader), {EncKey, EncIV} = init_down_encrypt(DownHeader),
Decrypt = init_down_decrypt(DownHeader), {DecKey, DecIV} = init_down_decrypt(DownHeader),
St = #st{decrypt = Decrypt, St = new(EncKey, EncIV, DecKey, DecIV),
encrypt = Encrypt},
{<<_:56/binary, Rep:8/binary, _/binary>>, St1} = encrypt(DownHeader, St), {<<_:56/binary, Rep:8/binary, _/binary>>, St1} = encrypt(DownHeader, St),
{ok, {ok,
<<Left/binary, Rep/binary>>, <<Left/binary, Rep/binary>>,
...@@ -57,30 +53,30 @@ new2(<<Left:56/binary, _/binary>> = DownHeader) -> ...@@ -57,30 +53,30 @@ new2(<<Left:56/binary, _/binary>> = DownHeader) ->
init_down_decrypt(<<_:8/binary, ToRev:48/binary, _/binary>>) -> init_down_decrypt(<<_:8/binary, ToRev:48/binary, _/binary>>) ->
Reversed = bin_rev(ToRev), Reversed = bin_rev(ToRev),
<<KeyRev:32/binary, RevIV:16/binary>> = Reversed, <<KeyRev:32/binary, RevIV:16/binary>> = Reversed,
?DBG("down-DEC Key: ~w;~nIV: ~w~n", [KeyRev, RevIV]), {KeyRev, RevIV}.
crypto:stream_init('aes_ctr', KeyRev, RevIV).
init_down_encrypt(<<_:8/binary, Key:32/binary, IV:16/binary, _/binary>>) -> init_down_encrypt(<<_:8/binary, Key:32/binary, IV:16/binary, _/binary>>) ->
?DBG("down-ENC Key: ~w;~nIV: ~w~n", [Key, IV]), {Key, IV}.
crypto:stream_init('aes_ctr', Key, IV).
%% @doc creates new obfuscated stream (MTProto proxy format) %% @doc creates new obfuscated stream (MTProto proxy format)
-spec from_header(binary(), binary()) -> {ok, inet:ip4_address(), codec()}. -spec from_header(binary(), binary()) -> {ok, inet:ip4_address(), codec()}.
from_header(Header, Secret) when byte_size(Header) == 64 -> from_header(Header, Secret) when byte_size(Header) == 64 ->
Encrypt = init_up_encrypt(Header, Secret), {EncKey, EncIV} = init_up_encrypt(Header, Secret),
Decrypt = init_up_decrypt(Header, Secret), {DecKey, DecIV} = init_up_decrypt(Header, Secret),
{Decrypt1, <<_:56/binary, Bin1:8/binary, _/binary>>} = crypto:stream_encrypt(Decrypt, Header), St = new(EncKey, EncIV, DecKey, DecIV),
{<<_:56/binary, Bin1:8/binary, _/binary>>, St1} = decrypt(Header, St),
<<HeaderPart:56/binary, _/binary>> = Header, <<HeaderPart:56/binary, _/binary>> = Header,
NewHeader = <<HeaderPart/binary, Bin1/binary>>, NewHeader = <<HeaderPart/binary, Bin1/binary>>,
case NewHeader of case NewHeader of
<<_:56/binary, 16#ef, 16#ef, 16#ef, 16#ef, _/binary>> -> <<_:56/binary, 16#ef, 16#ef, 16#ef, 16#ef, _/binary>> ->
Endpoint = get_endpoint(NewHeader), DcId = get_dc(NewHeader),
{ok, Endpoint, #st{decrypt = Decrypt1, {ok, DcId, St1};
encrypt = Encrypt}};
<<_:56/binary, 16#ee, 16#ee, 16#ee, 16#ee, _/binary>> -> <<_:56/binary, 16#ee, 16#ee, 16#ee, 16#ee, _/binary>> ->
metric:count_inc([?APP, protocol_error, total], 1, #{labels => [intermediate]}),
{error, {protocol_not_supported, intermediate}}; {error, {protocol_not_supported, intermediate}};
_ -> _ ->
metric:count_inc([?APP, protocol_error, total], 1, #{labels => [unknown]}),
{error, unknown_protocol} {error, unknown_protocol}
end. end.
...@@ -90,30 +86,44 @@ init_up_encrypt(Bin, Secret) -> ...@@ -90,30 +86,44 @@ init_up_encrypt(Bin, Secret) ->
<<KeyRev:32/binary, RevIV:16/binary, _/binary>> = Rev, <<KeyRev:32/binary, RevIV:16/binary, _/binary>> = Rev,
%% <<_:32/binary, RevIV:16/binary, _/binary>> = Bin, %% <<_:32/binary, RevIV:16/binary, _/binary>> = Bin,
KeyRevHash = crypto:hash('sha256', <<KeyRev/binary, Secret/binary>>), KeyRevHash = crypto:hash('sha256', <<KeyRev/binary, Secret/binary>>),
?DBG("up-ENC Key: ~p;~nIV: ~p~n", [KeyRevHash, RevIV]), {KeyRevHash, RevIV}.
crypto:stream_init('aes_ctr', KeyRevHash, RevIV).
init_up_decrypt(Bin, Secret) -> init_up_decrypt(Bin, Secret) ->
<<_:8/binary, Key:32/binary, _/binary>> = Bin, <<_:8/binary, Key:32/binary, IV:16/binary, _/binary>> = Bin,
<<_:40/binary, IV:16/binary, _/binary>> = Bin,
KeyHash = crypto:hash('sha256', <<Key/binary, Secret/binary>>), KeyHash = crypto:hash('sha256', <<Key/binary, Secret/binary>>),
?DBG("up-DEC Key: ~p;~nIV: ~p~n", [KeyHash, IV]), {KeyHash, IV}.
crypto:stream_init('aes_ctr', KeyHash, IV).
get_dc(<<_:60/binary, DcId:16/signed-little-integer, _/binary>>) ->
abs(DcId).
get_endpoint(<<_:60/binary, DcId:16/signed-little-integer, _/binary>>) -> new(EncKey, EncIV, DecKey, DecIV) ->
element(abs(DcId), ?ENDPOINTS). #st{decrypt = crypto:stream_init('aes_ctr', DecKey, DecIV),
encrypt = crypto:stream_init('aes_ctr', EncKey, EncIV)}.
-spec encrypt(iodata(), codec()) -> {binary(), codec()}.
encrypt(Data, #st{encrypt = Enc} = St) -> encrypt(Data, #st{encrypt = Enc} = St) ->
{Enc1, Encrypted} = crypto:stream_encrypt(Enc, Data), {Enc1, Encrypted} = crypto:stream_encrypt(Enc, Data),
?DBG("encrypt: IN:~p~nOUT:~p~n", [Data, Encrypted]),
{Encrypted, St#st{encrypt = Enc1}}. {Encrypted, St#st{encrypt = Enc1}}.
-spec decrypt(iodata(), codec()) -> {binary(), codec()}.
decrypt(Encrypted, #st{decrypt = Dec} = St) -> decrypt(Encrypted, #st{decrypt = Dec} = St) ->
{Dec1, Data} = crypto:stream_encrypt(Dec, Encrypted), {Dec1, Data} = crypto:stream_encrypt(Dec, Encrypted),
?DBG("decrypt: IN:~p~nOUT:~p~n", [Encrypted, Data]),
{Data, St#st{decrypt = Dec1}}. {Data, St#st{decrypt = Dec1}}.
%% To comply with mtp_layer interface
-spec try_decode_packet(iodata(), codec()) -> {ok, Decoded :: binary(), codec()}
| {incomplete, codec()}.
try_decode_packet(Encrypted, St) ->
{Decrypted, St1} = decrypt(Encrypted, St),
{ok, Decrypted, St1}.
-spec encode_packet(iodata(), codec()) -> {iodata(), codec()}.
encode_packet(Msg, S) ->
encrypt(Msg, S).
%% Helpers %% Helpers
bin_rev(Bin) -> bin_rev(Bin) ->
%% binary:encode_unsigned(binary:decode_unsigned(Bin, little)).
list_to_binary(lists:reverse(binary_to_list(Bin))). list_to_binary(lists:reverse(binary_to_list(Bin))).
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% MTProto RPC codec
%%% @end
%%% Created : 6 Jun 2018 by Sergey <me@seriyps.ru>
-module(mtp_rpc).
-behaviour(mtp_layer).
-export([new/5,
try_decode_packet/2,
encode_packet/2]).
-export([inet_pton/1]).
-export_type([codec/0]).
-record(rpc_st,
{client_addr :: binary(),
proxy_addr :: binary(),
proxy_tag :: binary(),
req_id = 1 :: non_neg_integer()}).
-define(APP, mtproto_proxy).
-define(RPC_PROXY_ANS, 13,218,3,68).
-define(RPC_CLOSE_EXT, 162,52,182,94).
-opaque codec() :: #rpc_st{}.
new(ClientIp, ClientPort, ProxyIp, ProxyPort, ProxyTag) ->
#rpc_st{client_addr = iolist_to_binary(encode_ip_port(ClientIp, ClientPort)),
proxy_addr = iolist_to_binary(encode_ip_port(ProxyIp, ProxyPort)),
proxy_tag = ProxyTag}.
%% It expects that packet segmentation was done on previous layer
try_decode_packet(<<?RPC_PROXY_ANS, _AnsFlags:4/binary, _ReqId:8/binary, Data/binary>> = _Msg, S) ->
{ok, Data, S};
try_decode_packet(<<?RPC_CLOSE_EXT, _/binary>> = _Msg, _S) ->
%% Use throw as short-circuit
throw(rpc_close);
try_decode_packet(<<>>, S) ->
{incomplete, S}.
encode_packet(Msg, #rpc_st{client_addr = ClientAddr, proxy_addr = ProxyAddr,
req_id = ReqId, proxy_tag = ProxyTag} = S) ->
((iolist_size(Msg) rem 4) == 0)
orelse error(not_aligned),
Req =
[<<238,241,206,54, %RPC_PROXY_REQ
8,16,2,64, %Flags
ReqId:64/little %ReqId
>>,
ClientAddr, ProxyAddr,
<<24:32/little, %ExtraSize
174,38,30,219, %ProxyTag
(byte_size(ProxyTag)),
ProxyTag/binary,
0, 0, 0 %Padding
>>
| Msg
],
{Req, S#rpc_st{req_id = ReqId + 1}}.
encode_ip_port(IPv4, Port) when tuple_size(IPv4) == 4 ->
IpBin = inet_pton(IPv4),
[lists:duplicate(10, <<0>>)
| <<255,255,
IpBin/binary,
Port:32/little>>];
encode_ip_port(IPv6, Port) when tuple_size(IPv6) == 8 ->
IpBin = inet_pton(IPv6),
[IpBin, <<Port:32/little>>].
inet_pton({X1, X2, X3, X4}) ->
<<X1, X2, X3, X4>>;
inet_pton(IPv6) when tuple_size(IPv6) == 8 ->
<< <<I:16/big-integer>> || I <- tuple_to_list(IPv6)>>.
-ifdef(TEST).
-include_lib("eunit/include/eunit.hrl").
tst_new() ->
ClientIp = {109, 238, 131, 159},
ClientPort = 1128,
ProxyIp = {80, 211, 29, 34},
ProxyPort = 53634,
ProxyTag = <<220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38>>,
new(ClientIp, ClientPort, ProxyIp, ProxyPort, ProxyTag).
decode_none_test() ->
S = tst_new(),
?assertEqual(
{incomplete, S}, try_decode_packet(<<>>, S)).
encode_test() ->
S = tst_new(),
Samples =
[{<<0,0,0,0,0,0,0,0,0,0,0,0,61,2,24,91,20,0,0,0,120,151,70,96,153,197,142,238,245,139,85,208,160,241,68,89,106,7,118,167>>,
<<238,241,206,54,8,16,2,64,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,255,255,109,238,131,159,104,4,0,0,0,0,0,0,0,0,0,0,0,0,255,255,80,211,29,34,130,209,0,0,24,0,0,0,174,38,30,219,16,220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,61,2,24,91,20,0,0,0,120,151,70,96,153,197,142,238,245,139,85,208,160,241,68,89,106,7,118,167>>},
{<<14,146,6,159,99,150,29,221,115,87,68,198,122,39,38,249,153,87,37,105,4,111,147,70,54,179,134,12,90,4,223,155,206,220,167,201,203,176,123,181,103,176,49,216,163,106,54,148,133,51,206,212,81,90,47,26,3,161,149,251,182,90,190,51,213,7,107,176,112,220,25,144,183,249,149,182,172,194,218,146,161,191,247,4,250,123,230,251,41,181,139,177,55,171,253,198,153,183,61,53,119,115,46,174,172,245,90,166,215,99,181,58,236,129,103,80,218,244,81,45,142,128,177,146,26,131,184,155,22,217,218,187,209,155,156,64,219,235,175,40,249,235,77,82,212,73,11,133,52,4,222,157,67,176,251,46,254,241,15,192,215,192,186,82,233,68,147,234,88,250,96,14,172,179,7,159,28,11,237,48,44,33,137,185,166,166,173,103,136,174,31,35,77,151,76,55,176,211,230,176,118,144,139,77,0,213,68,179,73,58,58,80,238,120,197,67,241,210,210,156,72,105,60,125,239,98,7,19,234,249,222,194,166,37,46,100,1,65,225,224,244,57,147,119,49,20,1,160,4,51,247,161,142,11,131,11,27,166,159,110,145,78,55,205,126,246,126,68,44,114,91,191,213,241,242,9,33,16,30,228>>,
<<238,241,206,54,8,16,2,64,2,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,255,255,109,238,131,159,104,4,0,0,0,0,0,0,0,0,0,0,0,0,255,255,80,211,29,34,130,209,0,0,24,0,0,0,174,38,30,219,16,220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38,0,0,0,14,146,6,159,99,150,29,221,115,87,68,198,122,39,38,249,153,87,37,105,4,111,147,70,54,179,134,12,90,4,223,155,206,220,167,201,203,176,123,181,103,176,49,216,163,106,54,148,133,51,206,212,81,90,47,26,3,161,149,251,182,90,190,51,213,7,107,176,112,220,25,144,183,249,149,182,172,194,218,146,161,191,247,4,250,123,230,251,41,181,139,177,55,171,253,198,153,183,61,53,119,115,46,174,172,245,90,166,215,99,181,58,236,129,103,80,218,244,81,45,142,128,177,146,26,131,184,155,22,217,218,187,209,155,156,64,219,235,175,40,249,235,77,82,212,73,11,133,52,4,222,157,67,176,251,46,254,241,15,192,215,192,186,82,233,68,147,234,88,250,96,14,172,179,7,159,28,11,237,48,44,33,137,185,166,166,173,103,136,174,31,35,77,151,76,55,176,211,230,176,118,144,139,77,0,213,68,179,73,58,58,80,238,120,197,67,241,210,210,156,72,105,60,125,239,98,7,19,234,249,222,194,166,37,46,100,1,65,225,224,244,57,147,119,49,20,1,160,4,51,247,161,142,11,131,11,27,166,159,110,145,78,55,205,126,246,126,68,44,114,91,191,213,241,242,9,33,16,30,228>>}],
lists:foldl(
fun({In, Out}, S1) ->
{Enc, S2} = encode_packet(In, S1),
?assertEqual(Out, iolist_to_binary(Enc)),
S2
end, S, Samples).
decode_test() ->
S = tst_new(),
Samples =
[{<<13,218,3,68,0,0,0,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,52,62,238,60,2,24,91,64,0,0,0,99,36,22,5,153,197,142,238,245,139,85,208,160,241,68,89,106,7,118,167,146,202,163,241,63,158,32,27,246,203,226,70,177,46,106,225,8,34,202,206,241,19,38,121,245,0,0,0,21,196,181,28,1,0,0,0,33,107,232,108,2,43,180,195>>,
<<0,0,0,0,0,0,0,0,1,52,62,238,60,2,24,91,64,0,0,0,99,36,22,5,153,197,142,238,245,139,85,208,160,241,68,89,106,7,118,167,146,202,163,241,63,158,32,27,246,203,226,70,177,46,106,225,8,34,202,206,241,19,38,121,245,0,0,0,21,196,181,28,1,0,0,0,33,107,232,108,2,43,180,195>>},
{<<13,218,3,68,0,0,0,0,2,0,0,0,0,0,0,0,14,146,6,159,99,150,29,221,85,233,237,52,236,18,11,0,174,214,89,213,69,89,250,18,116,192,128,240,217,221,210,144,123,9,182,152,60,206,88,187,101,178,53,107,44,98,190,195,149,114,0,19,90,218,101,133,183,249,183,170,90,21,86,24,42,81,224,152,13,58,90,84,41,158,177,99,57,83,123,99,138,127,29,238,162,49,71,65,165,168,218,220,245,202,24,135,152,1,28,38,85,197,8,232,201,163,65,118,202,89,204,67,48,21,51,106,188,7,167,61,185,82,39,210,164,21,97,99,63,167,2,143,69,126,214,75,95,142,69,68,243,49,11,121,28,177,159,0,154,134,206,34>>,
<<14,146,6,159,99,150,29,221,85,233,237,52,236,18,11,0,174,214,89,213,69,89,250,18,116,192,128,240,217,221,210,144,123,9,182,152,60,206,88,187,101,178,53,107,44,98,190,195,149,114,0,19,90,218,101,133,183,249,183,170,90,21,86,24,42,81,224,152,13,58,90,84,41,158,177,99,57,83,123,99,138,127,29,238,162,49,71,65,165,168,218,220,245,202,24,135,152,1,28,38,85,197,8,232,201,163,65,118,202,89,204,67,48,21,51,106,188,7,167,61,185,82,39,210,164,21,97,99,63,167,2,143,69,126,214,75,95,142,69,68,243,49,11,121,28,177,159,0,154,134,206,34>>}],
lists:foldl(
fun({In, Out}, S1) ->
{ok, Dec, S2} = try_decode_packet(In, S1),
?assertEqual(Out, iolist_to_binary(Dec)),
S2
end, S, Samples).
%% decode_close_test() ->
%% S = tst_new(),
%% In = <<>>,
%% ?assertError(rpc_close, try_decode_packet(In, S)).
-endif.
%%% @author Sergey <me@seriyps.ru>
%%% @copyright (C) 2018, Sergey
%%% @doc
%%% Abstraction that allows to wrap one mtp_layer into another mtp_layer
%%% @end
%%% Created : 6 Jun 2018 by Sergey <me@seriyps.ru>
-module(mtp_wrap).
-behaviour(mtp_layer).
-export([new/2,
try_decode_packet/2,
encode_packet/2]).
-export_type([codec/0]).
-record(wrap_st,
{outer :: mtp_layer:layer(),
inner :: mtp_layer:layer()}).
-define(APP, mtproto_proxy).
-opaque codec() :: #wrap_st{}.
new(Outer, Inner) ->
#wrap_st{outer = Outer,
inner = Inner}.
%% try_decode_packet(Inner) |> try_decode_packet(Outer)
try_decode_packet(Bin, #wrap_st{outer = Outer,
inner = Inner} = S) ->
{Dec1, Inner1} =
case mtp_layer:try_decode_packet(Bin, Inner) of
{incomplete, Inner1_} ->
%% We have to check if something is left in inner's buffers
{<<>>, Inner1_};
{ok, Dec1_, Inner1_} ->
{Dec1_, Inner1_}
end,
case mtp_layer:try_decode_packet(Dec1, Outer) of
{incomplete, Outer1} ->
{incomplete, S#wrap_st{inner = Inner1,
outer = Outer1}};
{ok, Dec2, Outer1} ->
{ok, Dec2, S#wrap_st{inner = Inner1,
outer = Outer1}}
end.
%% encode_packet(Outer) |> encode_packet(Inner)
encode_packet(Bin, #wrap_st{outer = Outer,
inner = Inner} = S) ->
{Enc1, Outer1} = mtp_layer:encode_packet(Bin, Outer),
{Enc2, Inner1} = mtp_layer:encode_packet(Enc1, Inner),
{Enc2, S#wrap_st{outer = Outer1, inner = Inner1}}.
...@@ -16,10 +16,14 @@ ...@@ -16,10 +16,14 @@
{ready_timeout_sec, 1200}, {ready_timeout_sec, 1200},
{ip, {0, 0, 0, 0}}, {ip, {0, 0, 0, 0}},
{ports, [{mtp_handler, 4430}]}, %% {external_ip, "YOUR.SERVER.EXTERNAL.IP"},
{ports, [#{name => mtp_handler,
port => 1443,
secret => <<208,214,225,17,186,218,85,17,252,206,149,132,222,173,190,239>>,
tag => <<220,190,143,20,147,250,76,217,171,48,8,145,192,181,179,38>>}]},
{num_acceptors, 60}, {num_acceptors, 60},
{max_connections, 1024}, {max_connections, 20480}
{secret, <<15,61,100,92,77,206,249,22,29,186,62,205,196,61,65,194>>}]}, ]},
{modules, []}, {modules, []},
{maintainers, []}, {maintainers, []},
......
...@@ -16,36 +16,35 @@ ...@@ -16,36 +16,35 @@
%%==================================================================== %%====================================================================
start(_StartType, _StartArgs) -> start(_StartType, _StartArgs) ->
Res = mtproto_proxy_sup:start_link(), Res = mtproto_proxy_sup:start_link(),
io:format("+++++++++++++++++++++++++++++++++++++++~n"
"Erlang MTProto proxy by @seriyps https://github.com/seriyps/mtproto_proxy~n"
"Sponsored by and powers @socksy_bot~n"),
[start_proxy(Where) || Where <- application:get_env(?APP, ports, [])], [start_proxy(Where) || Where <- application:get_env(?APP, ports, [])],
Res. Res.
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
stop(_State) -> stop(_State) ->
[stop_proxy(Where) || Where <- application:get_env(?APP, ports, [])],
ok. ok.
%%==================================================================== %%====================================================================
%% Internal functions %% Internal functions
%%==================================================================== %%====================================================================
start_proxy(#{name := Name, port := Port, secret := Secret, tag := Tag}) ->
start_proxy({Name, Port}) ->
ListenIp = application:get_env(?APP, ip, {0, 0, 0, 0}), ListenIp = application:get_env(?APP, ip, {0, 0, 0, 0}),
NumAcceptors = application:get_env(?APP, num_acceptors, 60), NumAcceptors = application:get_env(?APP, num_acceptors, 60),
MaxConnections = application:get_env(?APP, max_connections, 1024), MaxConnections = application:get_env(?APP, max_connections, 10240),
Res = {ok, Pid} = Res =
ranch:start_listener( ranch:start_listener(
Name, ranch_tcp, Name, ranch_tcp,
[{ip, ListenIp}, [{ip, ListenIp},
{port, Port}, {port, Port},
{num_acceptors, NumAcceptors}, {num_acceptors, NumAcceptors},
{max_connections, MaxConnections}], {max_connections, MaxConnections}],
mtp_handler, []), mtp_handler, [Secret, Tag]),
KeyStr = mtp_handler:key_str(), io:format("Proxy started on ~s:~p with key: ~s~n",
io:format("+++++++++++++++++++++++++++++++++++++++~n" [inet:ntoa(ListenIp), Port, mtp_handler:hex(Secret)]),
"Erlang MTProto proxy by @seriyps https://github.com/seriyps/mtproto_proxy~n"
"Sponsored by and powers @socksy_bot~n"
"Proxy started on ~s:~p with key: ~s~n~n"
"+++++++++++++++++++++++++++++++++++++++~n",
[inet:ntoa(ListenIp), Port, KeyStr]),
lager:info("mtproto=~p listening on addr=~s:~p with key ~s",
[Pid, inet:ntoa(ListenIp), Port, KeyStr]),
Res. Res.
stop_proxy(#{name := Name}) ->
ranch:stop_listener(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