Fix decoding of packets split to multiple TLS frames. Fixes gh-16

parent e0c07667
......@@ -113,13 +113,8 @@ decode_tls(Bin, #codec{have_tls = false} = S) ->
decode_tls(<<>>, #codec{tls_buf = <<>>} = S) ->
decode_crypto(<<>>, S);
decode_tls(Bin, #codec{tls_state = TlsSt, tls_buf = <<>>} = S) ->
case mtp_fake_tls:try_decode_packet(Bin, TlsSt) of
{incomplete, TlsSt1} ->
%% XXX: actually, TLS doesn't store any mutable state...
decode_crypto(<<>>, S#codec{tls_state = TlsSt1});
{ok, Dec, Tail, TlsSt1} ->
decode_crypto(Dec, assert_overflow(S#codec{tls_state = TlsSt1, tls_buf = Tail}))
end;
{DecIolist, Tail, TlsSt1} = mtp_fake_tls:decode_all(Bin, TlsSt),
decode_crypto(iolist_to_binary(DecIolist), assert_overflow(S#codec{tls_state = TlsSt1, tls_buf = Tail}));
decode_tls(Bin, #codec{tls_buf = Buf} = S) ->
decode_tls(<<Buf/binary, Bin/binary>>, S#codec{tls_buf = <<>>}).
......
......@@ -15,6 +15,7 @@
-export([from_client_hello/2,
new/0,
try_decode_packet/2,
decode_all/2,
encode_packet/2]).
-export_type([codec/0, meta/0]).
......@@ -176,18 +177,31 @@ new() ->
-spec try_decode_packet(binary(), codec()) -> {ok, binary(), binary(), codec()}
| {incomplete, codec()}.
try_decode_packet(<<?TLS_REC_DATA, ?TLS_12_VERSION, Size:16/unsigned-big,
try_decode_packet(<<?TLS_12_DATA, Size:16/unsigned-big,
Data:Size/binary, Tail/binary>>, St) ->
{ok, Data, Tail, St};
try_decode_packet(<<?TLS_REC_CHANGE_CIPHER, ?TLS_12_VERSION, Size:16/unsigned-big,
_Data:Size/binary, Tail/binary>>, St) ->
%% "Change cipher" are ignored
try_decode_packet(Tail, St);
try_decode_packet(Bin, St) when byte_size(Bin) =< ?MAX_PACKET_SIZE ->
try_decode_packet(Bin, St) when byte_size(Bin) =< (?MAX_PACKET_SIZE + 5) -> % 5 is ?TLS_12_DATA + Size:16 size
{incomplete, St};
try_decode_packet(Bin, _St) ->
error({protocol_error, tls_max_size, byte_size(Bin)}).
%% @doc decodes as much TLS packets as possible to single binary
-spec decode_all(binary(), codec()) -> {Decoded :: binary(), Tail :: binary(), codec()}.
decode_all(Bin, St) ->
decode_all(Bin, <<>>, St).
decode_all(Bin, Acc, St0) ->
case try_decode_packet(Bin, St0) of
{incomplete, St} ->
{Acc, Bin, St};
{ok, Data, Tail, St} ->
decode_all(Tail, <<Acc/binary, Data/binary>>, St)
end.
-spec encode_packet(binary(), codec()) -> {iodata(), codec()}.
encode_packet(Bin, St) ->
......
......@@ -8,6 +8,7 @@
stream_16b/0,
packet_16b/0,
binary/2,
aligned_binary/3,
key/0,
iv/0,
secret/0,
......@@ -36,11 +37,15 @@ stream_16b() ->
%% Binary of size between Min and Max
binary(Min, Max) when Min < Max ->
TailSize = Max - Min,
?LET({First, Tail}, {proper_types:binary(Min),
proper_types:resize(TailSize,
proper_types:list(proper_types:byte()))},
iolist_to_binary([First | Tail])).
?LET(Size, proper_types:integer(Min, Max), proper_types:binary(Size)).
%% Binary of size between Min and Max aligned by Align
aligned_binary(Align, Min0, Max0) when Min0 > Align,
Max0 > Min0 ->
Ceil = fun(V) -> V - (V rem Align) end,
Min = Ceil(Min0),
Max = Ceil(Max0),
?LET(Size, proper_types:integer(Min, Max), proper_types:binary(Ceil(Size))).
%% 32-byte encryption key: `binary()`
key() ->
......
......@@ -6,7 +6,9 @@
-export([prop_obfuscated_secure_stream/1,
prop_obfuscated_secure_duplex/1,
prop_obfuscated_secure_duplex_multi/1,
prop_fullcbc_stream/1]).
prop_fullcbc_stream/1,
prop_tls_stream/1,
prop_tls_big_stream/1]).
prop_obfuscated_secure_stream(doc) ->
......@@ -147,6 +149,48 @@ mk_fullcbc_codec(EncKey, EncIv, DecKey, DecIv) ->
mtp_codec:new(mtp_aes_cbc, Crypto,
mtp_full, Packet).
prop_tls_stream(doc) ->
"Tests combination of fake-tls + mtp_obfuscated + mtp_secure. It emulates fake-tls client".
prop_tls_stream() ->
?FORALL({Key, Iv, Stream}, stream_arg_set(), tls_obfuscated_secure_stream(Key, Iv, Stream)).
prop_tls_big_stream(doc) ->
"Tests combination of fake-tls + mtp_obfuscated + mtp_secure with packets >64kb. "
"So, single 'packet-layer' packet will be split to multiple TLS packets. "
"It emulates file uppload with fake-tls client".
prop_tls_big_stream() ->
?FORALL({Key, Iv, Stream}, tls_big_stream_arg_set(), tls_obfuscated_secure_stream(Key, Iv, Stream)).
tls_big_stream_arg_set() ->
%% Packets more than 64kb but less than 512kb
Min = 64 * 1024 + 10,
Max = 512 * 1024,
proper_types:tuple(
[mtp_prop_gen:key(),
mtp_prop_gen:iv(),
proper_types:list(mtp_prop_gen:aligned_binary(4, Min, Max))
]).
tls_obfuscated_secure_stream(Key, Iv, Stream) ->
Codec0 = mk_tls_codec(Key, Iv, Key, Iv),
{BinStream, Codec2} =
lists:foldl(
fun(Bin, {Acc, Codec1}) ->
{Data, Codec2} = mtp_codec:encode_packet(Bin, Codec1),
{<<Acc/binary, (iolist_to_binary(Data))/binary>>,
Codec2}
end, {<<>>, Codec0}, Stream),
{ResStream, _Codec3} = parse_stream(BinStream, Codec2),
?assertEqual(Stream, ResStream),
true.
parse_stream(Bin, Codec0) ->
%% We want to split solid stream to smaller chunks to emulate network packet fragmentation
Chunks = split_stream(Bin),
......@@ -162,6 +206,15 @@ parse_stream(Bin, Codec0) ->
end, {[], Codec0}, Chunks),
{lists:reverse(DecodedRev), Codec}.
mk_tls_codec(EncKey, EncIv, DecKey, DecIv) ->
Crypto = mtp_obfuscated:new(EncKey, EncIv, DecKey, DecIv),
Packet = mtp_secure:new(),
Tls = mtp_fake_tls:new(),
mtp_codec:new(mtp_obfuscated, Crypto,
mtp_secure, Packet,
true, Tls,
30 * 1024 * 1024).
split_stream(<<>>) -> [];
split_stream(Bin) when byte_size(Bin) < 4 -> [Bin];
split_stream(Bin) ->
......
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