Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
0590-ssl-Remove-use-of-non-recommended-function...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0590-ssl-Remove-use-of-non-recommended-function-size.patch of Package erlang
From 593472da5da198820300fd16540383a12c35e1ad Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin <ingela@erlang.org> Date: Tue, 20 Jul 2021 12:04:34 +0200 Subject: [PATCH] ssl: Remove use of non recommended function size --- lib/ssl/src/dtls_handshake.erl | 4 ++-- lib/ssl/src/dtls_record.erl | 2 +- lib/ssl/src/ssl_handshake.erl | 4 ++-- lib/ssl/src/tls_gen_connection.erl | 4 ++-- lib/ssl/src/tls_handshake_1_3.erl | 4 ++-- lib/ssl/src/tls_v1.erl | 4 ++-- lib/ssl/test/ssl_packet_SUITE.erl | 8 ++++---- lib/ssl/test/ssl_test_lib.erl | 2 +- lib/ssl/test/tls_1_3_record_SUITE.erl | 2 +- 9 files changed, 17 insertions(+), 17 deletions(-) diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl index af053ef48c..b8f9d7f42b 100644 --- a/lib/ssl/src/dtls_handshake.erl +++ b/lib/ssl/src/dtls_handshake.erl @@ -287,7 +287,7 @@ handshake_bin(Type, Length, Seq, FragmentData) -> FragmentData:Length/binary>>. bin_fragments(Bin, Size) -> - bin_fragments(Bin, size(Bin), Size, 0, []). + bin_fragments(Bin, byte_size(Bin), Size, 0, []). bin_fragments(Bin, BinSize, FragSize, Offset, Fragments) -> case (BinSize - Offset - FragSize) > 0 of true -> @@ -301,7 +301,7 @@ bin_fragments(Bin, BinSize, FragSize, Offset, Fragments) -> handshake_fragments(_, _, _, [], Acc) -> lists:reverse(Acc); handshake_fragments(MsgType, Seq, Len, [{Bin, Offset} | Bins], Acc) -> - FragLen = size(Bin), + FragLen = byte_size(Bin), handshake_fragments(MsgType, Seq, Len, Bins, [<<?BYTE(MsgType), Len/binary, Seq/binary, ?UINT24(Offset), ?UINT24(FragLen), Bin/binary>> | Acc]). diff --git a/lib/ssl/src/dtls_record.erl b/lib/ssl/src/dtls_record.erl index 16542a8eb3..dda8055cbf 100644 --- a/lib/ssl/src/dtls_record.erl +++ b/lib/ssl/src/dtls_record.erl @@ -457,7 +457,7 @@ get_dtls_records_aux(_, <<?BYTE(_), ?BYTE(_MajVer), ?BYTE(_MinVer), ?ALERT_REC(?FATAL, ?RECORD_OVERFLOW); get_dtls_records_aux(_, Data, Acc, _) -> - case size(Data) =< ?MAX_CIPHER_TEXT_LENGTH + ?INITIAL_BYTES of + case byte_size(Data) =< ?MAX_CIPHER_TEXT_LENGTH + ?INITIAL_BYTES of true -> {lists:reverse(Acc), Data}; false -> diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 9e5ef2d8f3..32436fdae0 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2313,7 +2313,7 @@ encode_server_key(#server_dh_params{dh_p = P, dh_g = G, dh_y = Y}) -> <<?UINT16(PLen), P/binary, ?UINT16(GLen), G/binary, ?UINT16(YLen), Y/binary>>; encode_server_key(#server_ecdh_params{curve = {namedCurve, ECCurve}, public = ECPubKey}) -> %%TODO: support arbitrary keys - KLen = size(ECPubKey), + KLen = byte_size(ECPubKey), <<?BYTE(?NAMED_CURVE), ?UINT16((tls_v1:oid_to_enum(ECCurve))), ?BYTE(KLen), ECPubKey/binary>>; encode_server_key(#server_psk_params{hint = PskIdentityHint}) -> @@ -2338,7 +2338,7 @@ encode_server_key(#server_ecdhe_psk_params{ curve = {namedCurve, ECCurve}, public = ECPubKey}}) -> %%TODO: support arbitrary keys Len = byte_size(PskIdentityHint), - KLen = size(ECPubKey), + KLen = byte_size(ECPubKey), <<?UINT16(Len), PskIdentityHint/binary, ?BYTE(?NAMED_CURVE), ?UINT16((tls_v1:oid_to_enum(ECCurve))), ?BYTE(KLen), ECPubKey/binary>>; diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl index ae5b0e375e..fa8972e833 100644 --- a/lib/ssl/src/tls_gen_connection.erl +++ b/lib/ssl/src/tls_gen_connection.erl @@ -735,7 +735,7 @@ effective_version(Version, _, _) -> assert_buffer_sanity(<<?BYTE(_Type), ?UINT24(Length), Rest/binary>>, #{max_handshake_size := Max}) when Length =< Max -> - case size(Rest) of + case byte_size(Rest) of N when N < Length -> true; N when N > Length -> @@ -746,7 +746,7 @@ assert_buffer_sanity(<<?BYTE(_Type), ?UINT24(Length), Rest/binary>>, malformed_handshake_data)) end; assert_buffer_sanity(Bin, _) -> - case size(Bin) of + case byte_size(Bin) of N when N < 3 -> true; _ -> diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl index 950d694b12..c14e44a7fa 100644 --- a/lib/ssl/src/tls_handshake_1_3.erl +++ b/lib/ssl/src/tls_handshake_1_3.erl @@ -2603,7 +2603,7 @@ truncate_client_hello(HelloBin0) -> %% Return the truncated ClientHello by cutting of the binders from the original %% ClientHello binary. - {Truncated, _} = split_binary(HelloBin0, size(HelloBin0) - BindersSize - 2), + {Truncated, _} = split_binary(HelloBin0, byte_size(HelloBin0) - BindersSize - 2), Truncated. maybe_add_early_data_indication(#client_hello{ @@ -2612,7 +2612,7 @@ maybe_add_early_data_indication(#client_hello{ Version) when Version =:= {3,4} andalso is_binary(EarlyData) andalso - size(EarlyData) > 0 -> + byte_size(EarlyData) > 0 -> Extensions = Extensions0#{early_data => #early_data_indication{}}, ClientHello#client_hello{extensions = Extensions}; diff --git a/lib/ssl/src/tls_v1.erl b/lib/ssl/src/tls_v1.erl index 1253a960c2..14c1311a52 100644 --- a/lib/ssl/src/tls_v1.erl +++ b/lib/ssl/src/tls_v1.erl @@ -117,9 +117,9 @@ create_info(Label0, Context0, Length) -> %% opaque context<0..255> = Context; %% } HkdfLabel; Label1 = << <<"tls13 ">>/binary, Label0/binary>>, - LabelLen = size(Label1), + LabelLen = byte_size(Label1), Label = <<?BYTE(LabelLen), Label1/binary>>, - ContextLen = size(Context0), + ContextLen = byte_size(Context0), Context = <<?BYTE(ContextLen),Context0/binary>>, Content = <<Label/binary, Context/binary>>, <<?UINT16(Length), Content/binary>>. diff --git a/lib/ssl/test/ssl_packet_SUITE.erl b/lib/ssl/test/ssl_packet_SUITE.erl index a65173f172..db3a56a413 100644 --- a/lib/ssl/test/ssl_packet_SUITE.erl +++ b/lib/ssl/test/ssl_packet_SUITE.erl @@ -218,7 +218,7 @@ -define(UINT24(X), X:24/unsigned-big-integer). -define(UINT32(X), X:32/unsigned-big-integer). -define(UINT64(X), X:64/unsigned-big-integer). --define(STRING(X), ?UINT32((size(X))), (X)/binary). +-define(STRING(X), ?UINT32((byte_size(X))), (X)/binary). -define(byte(X), << ?BYTE(X) >> ). -define(uint16(X), << ?UINT16(X) >> ). @@ -2246,7 +2246,7 @@ send_incomplete(Socket, _Data, 0, Prev) -> ssl:send(Socket, [?uint32(0)]), no_result_msg; send_incomplete(Socket, Data, N, Prev) -> - Length = size(Data), + Length = byte_size(Data), <<Part1:42/binary, Rest/binary>> = Data, ssl:send(Socket, [Prev, ?uint32(Length), Part1]), send_incomplete(Socket, Data, N-1, Rest). @@ -2436,11 +2436,11 @@ client_line_packet_decode(Socket, P1, P2, L1, L2) -> end. add_tpkt_header(Data) when is_binary(Data) -> - L = size(Data) + 4, + L = byte_size(Data) + 4, [3, 0, ((L) bsr 8) band 16#ff, (L) band 16#ff ,Data]; add_tpkt_header(IOList) when is_list(IOList) -> Binary = list_to_binary(IOList), - L = size(Binary) + 4, + L = byte_size(Binary) + 4, [3, 0, ((L) bsr 8) band 16#ff, (L) band 16#ff , Binary]. diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl index da8f408b0a..17a04fb374 100644 --- a/lib/ssl/test/ssl_test_lib.erl +++ b/lib/ssl/test/ssl_test_lib.erl @@ -2880,7 +2880,7 @@ active_recv(Socket, N, Acc) -> data_length(Bytes) when is_list(Bytes) -> length(Bytes); data_length(Bytes) when is_binary(Bytes)-> - size(Bytes). + byte_size(Bytes). filter_openssl_debug_data(Bytes) -> re:replace(Bytes, diff --git a/lib/ssl/test/tls_1_3_record_SUITE.erl b/lib/ssl/test/tls_1_3_record_SUITE.erl index f5f57b534b..ab6d7bf33b 100644 --- a/lib/ssl/test/tls_1_3_record_SUITE.erl +++ b/lib/ssl/test/tls_1_3_record_SUITE.erl @@ -1430,7 +1430,7 @@ finished_verify_data(_Config) -> hexstr2int(S) -> B = hexstr2bin(S), - Bits = size(B) * 8, + Bits = byte_size(B) * 8, <<Integer:Bits/integer>> = B, Integer. -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor