Migrate to more modern OTP versions (remove OTP-20, add OTP-23,24)

parent 5ad7c536
sudo: required sudo: required
language: erlang language: erlang
otp_release: otp_release:
- 22.0 - 23.3.1
- 22.3
- 21.3 - 21.3
- 21.0 #- 20.3 not supported (erlang:get_stacktrace/0)
- 20.3
#- 19.3 not supported (string:lexemes/2) #- 19.3 not supported (string:lexemes/2)
#- 18.3 not supported (string:lexemes/2, tricky binary comprehension, map typespec with `:=`, ?assertEqual/3) #- 18.3 not supported (string:lexemes/2, tricky binary comprehension, map typespec with `:=`, ?assertEqual/3)
install: install:
......
...@@ -5,11 +5,11 @@ ...@@ -5,11 +5,11 @@
{deps, [{ranch, "1.7.0"}, {deps, [{ranch, "1.7.0"},
{hut, "1.3.0"}, {hut, "1.3.0"},
{lager, "3.6.3"}, {lager, "3.9.1"},
{erlang_psq, "1.0.0"} {erlang_psq, "1.0.0"}
]}. ]}.
{plugins, [rebar3_proper, {project_plugins, [rebar3_proper,
rebar3_bench] rebar3_bench]
}. }.
{xref_checks, {xref_checks,
......
{"1.1.0", {"1.2.0",
[{<<"erlang_psq">>,{pkg,<<"erlang_psq">>,<<"1.0.0">>},0}, [{<<"erlang_psq">>,{pkg,<<"erlang_psq">>,<<"1.0.0">>},0},
{<<"goldrush">>,{pkg,<<"goldrush">>,<<"0.1.9">>},1}, {<<"goldrush">>,{pkg,<<"goldrush">>,<<"0.1.9">>},1},
{<<"hut">>,{pkg,<<"hut">>,<<"1.3.0">>},0}, {<<"hut">>,{pkg,<<"hut">>,<<"1.3.0">>},0},
{<<"lager">>,{pkg,<<"lager">>,<<"3.6.3">>},0}, {<<"lager">>,{pkg,<<"lager">>,<<"3.9.1">>},0},
{<<"ranch">>,{pkg,<<"ranch">>,<<"1.7.0">>},0}]}. {<<"ranch">>,{pkg,<<"ranch">>,<<"1.7.0">>},0}]}.
[ [
{pkg_hash,[ {pkg_hash,[
{<<"erlang_psq">>, <<"995E328461A5949A54BDFC7686609A08EFB82313914F9AEAD494A2644629EA26">>}, {<<"erlang_psq">>, <<"995E328461A5949A54BDFC7686609A08EFB82313914F9AEAD494A2644629EA26">>},
{<<"goldrush">>, <<"F06E5D5F1277DA5C413E84D5A2924174182FB108DABB39D5EC548B27424CD106">>}, {<<"goldrush">>, <<"F06E5D5F1277DA5C413E84D5A2924174182FB108DABB39D5EC548B27424CD106">>},
{<<"hut">>, <<"71F2F054E657C03F959CF1ACC43F436EA87580696528CA2A55C8AFB1B06C85E7">>}, {<<"hut">>, <<"71F2F054E657C03F959CF1ACC43F436EA87580696528CA2A55C8AFB1B06C85E7">>},
{<<"lager">>, <<"FE78951D174616273F87F0DBC3374D1430B1952E5EFC4E1C995592D30A207294">>}, {<<"lager">>, <<"5885BC71308CD38F9D025C8ECDE4E5CCE1CE8565F80BFC6199865C845D6DBE95">>},
{<<"ranch">>, <<"9583F47160CA62AF7F8D5DB11454068EAA32B56EEADF984D4F46E61A076DF5F2">>}]} {<<"ranch">>, <<"9583F47160CA62AF7F8D5DB11454068EAA32B56EEADF984D4F46E61A076DF5F2">>}]},
{pkg_hash_ext,[
{<<"erlang_psq">>, <<"03DA24C3AA84313D57603B6A4B51EB46B4B787FA95BF5668D03E101A466DDFB2">>},
{<<"goldrush">>, <<"99CB4128CFFCB3227581E5D4D803D5413FA643F4EB96523F77D9E6937D994CEB">>},
{<<"hut">>, <<"7E15D28555D8A1F2B5A3A931EC120AF0753E4853A4C66053DB354F35BF9AB563">>},
{<<"lager">>, <<"3F59BA75A04A99E5F18BF91C89F46DCE536F83C6CB415FE26E6E75A62BEF37DC">>},
{<<"ranch">>, <<"59F7501C3A56125B2FC5684C3048FAC9D043C0BF4D173941B12CA927949AF189">>}]}
]. ].
No preview for this file type
...@@ -30,17 +30,17 @@ ...@@ -30,17 +30,17 @@
new(EncKey, EncIv, DecKey, DecIv, BlockSize) -> new(EncKey, EncIv, DecKey, DecIv, BlockSize) ->
#baes_st{ #baes_st{
block_size = BlockSize, block_size = BlockSize,
encrypt = {EncKey, EncIv}, encrypt = cbc_init(EncKey, EncIv, true),
decrypt = {DecKey, DecIv} decrypt = cbc_init(DecKey, DecIv, false)
}. }.
-spec encrypt(iodata(), codec()) -> {binary(), codec()}. -spec encrypt(iodata(), codec()) -> {binary(), codec()}.
encrypt(Data, #baes_st{block_size = BSize, encrypt(Data, #baes_st{block_size = BSize,
encrypt = {EncKey, EncIv}} = S) -> encrypt = Enc} = S) ->
((iolist_size(Data) rem BSize) == 0) ((iolist_size(Data) rem BSize) == 0)
orelse error({data_not_aligned, BSize, byte_size(Data)}), orelse error({data_not_aligned, BSize, byte_size(Data)}),
Encrypted = crypto:block_encrypt(aes_cbc, EncKey, EncIv, Data), {Enc1, Encrypted} = cbc_encrypt(Enc, Data),
{Encrypted, S#baes_st{encrypt = {EncKey, crypto:next_iv(aes_cbc, Encrypted)}}}. {Encrypted, S#baes_st{encrypt = Enc1}}.
-spec decrypt(binary(), codec()) -> {Data :: binary(), Tail :: binary(), codec()}. -spec decrypt(binary(), codec()) -> {Data :: binary(), Tail :: binary(), codec()}.
...@@ -62,10 +62,9 @@ decrypt(Data, #baes_st{block_size = BSize} = S) -> ...@@ -62,10 +62,9 @@ decrypt(Data, #baes_st{block_size = BSize} = S) ->
do_decrypt(ToDecode, Reminder, S) do_decrypt(ToDecode, Reminder, S)
end. end.
do_decrypt(Data, Tail, #baes_st{decrypt = {DecKey, DecIv}} = S) -> do_decrypt(Data, Tail, #baes_st{decrypt = Dec} = S) ->
Decrypted = crypto:block_decrypt(aes_cbc, DecKey, DecIv, Data), {Dec1, Decrypted} = cbc_decrypt(Dec, Data),
NewDecIv = crypto:next_iv(aes_cbc, Data), {Decrypted, Tail, S#baes_st{decrypt = Dec1}}.
{Decrypted, Tail, S#baes_st{decrypt = {DecKey, NewDecIv}}}.
try_decode_packet(Bin, S) -> try_decode_packet(Bin, S) ->
case decrypt(Bin, S) of case decrypt(Bin, S) of
...@@ -78,6 +77,32 @@ try_decode_packet(Bin, S) -> ...@@ -78,6 +77,32 @@ try_decode_packet(Bin, S) ->
encode_packet(Bin, S) -> encode_packet(Bin, S) ->
encrypt(Bin, S). encrypt(Bin, S).
-if(?OTP_RELEASE >= 23).
cbc_init(Key, IV, IsEncrypt) ->
crypto:crypto_init(aes_256_cbc, Key, IV, [{encrypt, IsEncrypt}]).
cbc_encrypt(State, Data) ->
%% Assuming state was created with {encrypt, true}
{State, crypto:crypto_update(State, Data)}.
cbc_decrypt(State, Data) ->
%% Assuming state was created with {encrypt, false}
{State, crypto:crypto_update(State, Data)}.
-else.
cbc_init(Key, IV, _IsEncrypt) ->
{Key, IV}.
cbc_encrypt({EncKey, EncIv}, Data) ->
Encrypted = crypto:block_encrypt(aes_cbc, EncKey, EncIv, Data),
{{EncKey, crypto:next_iv(aes_cbc, Encrypted)}, Encrypted}.
cbc_decrypt({DecKey, DecIv}, Data) ->
Decrypted = crypto:block_decrypt(aes_cbc, DecKey, DecIv, Data),
NewDecIv = crypto:next_iv(aes_cbc, Data),
{{DecKey, NewDecIv}, Decrypted}.
-endif.
-ifdef(TEST). -ifdef(TEST).
-include_lib("eunit/include/eunit.hrl"). -include_lib("eunit/include/eunit.hrl").
......
...@@ -45,12 +45,6 @@ ...@@ -45,12 +45,6 @@
-record(state, {tab :: ets:tid(), -record(state, {tab :: ets:tid(),
timer :: gen_timeout:tout()}). timer :: gen_timeout:tout()}).
-ifndef(OTP_RELEASE). % pre-OTP21
-define(WITH_STACKTRACE(T, R, S), T:R -> S = erlang:get_stacktrace(), ).
-else.
-define(WITH_STACKTRACE(T, R, S), T:R:S ->).
-endif.
%%%=================================================================== %%%===================================================================
%%% API %%% API
%%%=================================================================== %%%===================================================================
...@@ -182,7 +176,7 @@ update(#state{tab = Tab}, force) -> ...@@ -182,7 +176,7 @@ update(#state{tab = Tab}, force) ->
update_config(Tab); update_config(Tab);
update(State, _) -> update(State, _) ->
try update(State, force) try update(State, force)
catch ?WITH_STACKTRACE(Class, Reason, Stack) catch Class:Reason:Stack ->
?log(error, "Err updating proxy settings: ~s", ?log(error, "Err updating proxy settings: ~s",
[lager:pr_stacktrace(Stack, {Class, Reason})]) %XXX lager-specific [lager:pr_stacktrace(Stack, {Class, Reason})]) %XXX lager-specific
end. end.
...@@ -254,7 +248,7 @@ update_ip([Url | Fallbacks]) -> ...@@ -254,7 +248,7 @@ update_ip([Url | Fallbacks]) ->
IpStr= string:trim(Body), IpStr= string:trim(Body),
{ok, _} = inet:parse_ipv4strict_address(IpStr), %assert {ok, _} = inet:parse_ipv4strict_address(IpStr), %assert
application:set_env(?APP, external_ip, IpStr) application:set_env(?APP, external_ip, IpStr)
catch ?WITH_STACKTRACE(Class, Reason, Stack) catch Class:Reason:Stack ->
?log(error, "Failed to update IP with ~s service: ~s", ?log(error, "Failed to update IP with ~s service: ~s",
[Url, lager:pr_stacktrace(Stack, {Class, Reason})]), %XXX - lager-specific [Url, lager:pr_stacktrace(Stack, {Class, Reason})]), %XXX - lager-specific
update_ip(Fallbacks) update_ip(Fallbacks)
...@@ -272,7 +266,9 @@ update_ip([]) -> ...@@ -272,7 +266,9 @@ update_ip([]) ->
http_get(Url) -> http_get(Url) ->
{ok, Vsn} = application:get_key(mtproto_proxy, vsn), {ok, Vsn} = application:get_key(mtproto_proxy, vsn),
UserAgent = "MTProtoProxy/" ++ Vsn ++ " (+https://github.com/seriyps/mtproto_proxy)", OtpVersion = erlang:system_info(otp_release),
UserAgent = ("MTProtoProxy/" ++ Vsn ++ " OTP-" ++ OtpVersion ++
" (+https://github.com/seriyps/mtproto_proxy)"),
Headers = [{"User-Agent", UserAgent}], Headers = [{"User-Agent", UserAgent}],
{ok, {{_, 200, _}, _, Body}} = {ok, {{_, 200, _}, _, Body}} =
httpc:request(get, {Url, Headers}, [{timeout, 3000}], ?OPTS), httpc:request(get, {Url, Headers}, [{timeout, 3000}], ?OPTS),
......
...@@ -38,12 +38,6 @@ ...@@ -38,12 +38,6 @@
-define(MAX_CODEC_BUFFERS, 5 * 1024 * 1024). -define(MAX_CODEC_BUFFERS, 5 * 1024 * 1024).
-define(DEFAULT_CLIENTS_PER_CONN, 300). -define(DEFAULT_CLIENTS_PER_CONN, 300).
-ifndef(OTP_RELEASE). % pre-OTP21
-define(WITH_STACKTRACE(T, R, S), T:R -> S = erlang:get_stacktrace(), ).
-else.
-define(WITH_STACKTRACE(T, R, S), T:R:S ->).
-endif.
-type handle() :: pid(). -type handle() :: pid().
-type upstream_opts() :: #{addr := mtp_config:netloc_v4v6(), % IP/Port of TG client -type upstream_opts() :: #{addr := mtp_config:netloc_v4v6(), % IP/Port of TG client
ad_tag => binary()}. ad_tag => binary()}.
...@@ -169,7 +163,7 @@ handle_info(do_connect, #state{dc_id = DcId} = State) -> ...@@ -169,7 +163,7 @@ handle_info(do_connect, #state{dc_id = DcId} = State) ->
try try
{ok, St1} = connect(DcId, State), {ok, St1} = connect(DcId, State),
{noreply, St1} {noreply, St1}
catch ?WITH_STACKTRACE(Class, Reason, Stack) catch Class:Reason:Stack ->
?log(error, "Down connect to dc=~w error: ~s", ?log(error, "Down connect to dc=~w error: ~s",
[DcId, lager:pr_stacktrace(Stack, {Class, Reason})]), %XXX lager-specific [DcId, lager:pr_stacktrace(Stack, {Class, Reason})]), %XXX lager-specific
erlang:send_after(300, self(), do_connect), erlang:send_after(300, self(), do_connect),
......
...@@ -119,7 +119,7 @@ from_client_hello(Data, Secret) -> ...@@ -119,7 +119,7 @@ from_client_hello(Data, Secret) ->
[as_tls_frame(?TLS_REC_HANDSHAKE, SrvHello0), [as_tls_frame(?TLS_REC_HANDSHAKE, SrvHello0),
as_tls_frame(?TLS_REC_CHANGE_CIPHER, [1]), as_tls_frame(?TLS_REC_CHANGE_CIPHER, [1]),
as_tls_frame(?TLS_REC_DATA, FakeHttpData)], as_tls_frame(?TLS_REC_DATA, FakeHttpData)],
SrvHelloDigest = crypto:hmac(sha256, Secret, [ClientDigest | Response0]), SrvHelloDigest = hmac(sha256, Secret, [ClientDigest | Response0]),
SrvHello = make_srv_hello(SrvHelloDigest, SessionId, KeyShare), SrvHello = make_srv_hello(SrvHelloDigest, SessionId, KeyShare),
Response = [as_tls_frame(?TLS_REC_HANDSHAKE, SrvHello), Response = [as_tls_frame(?TLS_REC_HANDSHAKE, SrvHello),
CC, CC,
...@@ -174,7 +174,7 @@ parse_extension(_Type, Data) -> ...@@ -174,7 +174,7 @@ parse_extension(_Type, Data) ->
make_server_digest(<<Left:?DIGEST_POS/binary, _:?DIGEST_LEN/binary, Right/binary>>, Secret) -> make_server_digest(<<Left:?DIGEST_POS/binary, _:?DIGEST_LEN/binary, Right/binary>>, Secret) ->
Msg = [Left, binary:copy(<<0>>, ?DIGEST_LEN), Right], Msg = [Left, binary:copy(<<0>>, ?DIGEST_LEN), Right],
crypto:hmac(sha256, Secret, Msg). hmac(sha256, Secret, Msg).
make_key_share(Exts) -> make_key_share(Exts) ->
case lists:keyfind(?EXT_KEY_SHARE, 1, Exts) of case lists:keyfind(?EXT_KEY_SHARE, 1, Exts) of
...@@ -276,7 +276,7 @@ make_client_hello(Timestamp, SessionId, Secret, SniDomain) when byte_size(Sessio ...@@ -276,7 +276,7 @@ make_client_hello(Timestamp, SessionId, Secret, SniDomain) when byte_size(Sessio
end, end,
FakeRandom0 = binary:copy(<<0>>, ?DIGEST_LEN), FakeRandom0 = binary:copy(<<0>>, ?DIGEST_LEN),
Hello0 = Pack(FakeRandom0), Hello0 = Pack(FakeRandom0),
Digest = crypto:hmac(sha256, Secret, Hello0), Digest = hmac(sha256, Secret, Hello0),
EncTimestamp = <<(binary:copy(<<0>>, ?DIGEST_LEN - 4))/binary, Timestamp:32/unsigned-little>>, EncTimestamp = <<(binary:copy(<<0>>, ?DIGEST_LEN - 4))/binary, Timestamp:32/unsigned-little>>,
FakeRandom = crypto:exor(Digest, EncTimestamp), FakeRandom = crypto:exor(Digest, EncTimestamp),
Pack(FakeRandom). Pack(FakeRandom).
...@@ -355,3 +355,11 @@ as_tls_data_frame(Bin) -> ...@@ -355,3 +355,11 @@ as_tls_data_frame(Bin) ->
as_tls_frame(Type, Data) -> as_tls_frame(Type, Data) ->
Size = iolist_size(Data), Size = iolist_size(Data),
[<<Type, ?TLS_12_VERSION, Size:?u16>> | Data]. [<<Type, ?TLS_12_VERSION, Size:?u16>> | Data].
-if(?OTP_RELEASE >= 23).
hmac(Algo, Key, Str) ->
crypto:mac(hmac, Algo, Key, Str).
-else.
hmac(Algo, Key, Str) ->
crypto:hmac(Algo, Key, Str).
-endif.
...@@ -153,17 +153,17 @@ get_dc(<<_:4/binary, DcId:16/signed-little-integer>>) -> ...@@ -153,17 +153,17 @@ get_dc(<<_:4/binary, DcId:16/signed-little-integer>>) ->
new(EncKey, EncIV, DecKey, DecIV) -> new(EncKey, EncIV, DecKey, DecIV) ->
#st{decrypt = crypto:stream_init('aes_ctr', DecKey, DecIV), #st{decrypt = crypto_stream_init('aes_ctr', DecKey, DecIV),
encrypt = crypto:stream_init('aes_ctr', EncKey, EncIV)}. encrypt = crypto_stream_init('aes_ctr', EncKey, EncIV)}.
-spec encrypt(iodata(), codec()) -> {binary(), codec()}. -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),
{Encrypted, St#st{encrypt = Enc1}}. {Encrypted, St#st{encrypt = Enc1}}.
-spec decrypt(iodata(), codec()) -> {binary(), binary(), codec()}. -spec decrypt(iodata(), codec()) -> {binary(), 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),
{Data, <<>>, St#st{decrypt = Dec1}}. {Data, <<>>, St#st{decrypt = Dec1}}.
-spec try_decode_packet(iodata(), codec()) -> {ok, Decoded :: binary(), Tail :: binary(), codec()} -spec try_decode_packet(iodata(), codec()) -> {ok, Decoded :: binary(), Tail :: binary(), codec()}
...@@ -182,6 +182,22 @@ bin_rev(Bin) -> ...@@ -182,6 +182,22 @@ bin_rev(Bin) ->
%% binary:encode_unsigned(binary:decode_unsigned(Bin, little)). %% 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))).
-if(?OTP_RELEASE >= 23).
crypto_stream_init(aes_ctr, Key, IV) ->
crypto:crypto_init(aes_256_ctr, Key, IV, []).
crypto_stream_encrypt(State, Data) ->
{State, crypto:crypto_update(State, Data)}.
-else.
crypto_stream_init(Algo, Key, IV) ->
crypto:stream_init(Algo, Key, IV).
crypto_stream_encrypt(State, Data) ->
crypto:stream_encrypt(State, Data).
-endif.
-ifdef(TEST). -ifdef(TEST).
-include_lib("eunit/include/eunit.hrl"). -include_lib("eunit/include/eunit.hrl").
......
{application, mtproto_proxy, {application, mtproto_proxy,
[{description, "High-performance Telegram MTProto proxy server"}, [{description, "High-performance Telegram MTProto proxy server"},
{vsn, "0.7.0"}, {vsn, "0.7.1"},
{registered, []}, {registered, []},
{mod, { mtproto_proxy_app, []}}, {mod, { mtproto_proxy_app, []}},
{applications, {applications,
......
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