File 1247-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
@@ -255,7 +255,7 @@ handshake_bin(Type, Length, Seq, FragmentData) ->
     ssl_handshake:encode_handshake(HandshakeMsg, Version).
 
 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
@@ -270,7 +270,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
@@ -445,7 +445,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
@@ -1565,7 +1565,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}) ->
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index ae5b0e375e..fa8972e833 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -775,7 +775,7 @@ effective_version(Version, _, _) ->
 
 assert_buffer_sanity(<<?BYTE(_Type), ?UINT24(Length), Rest/binary>>, #ssl_options{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 ->       
@@ -786,7 +786,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/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
@@ -31,7 +31,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) >> ).
@@ -2001,7 +2001,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).
@@ -2204,9 +2204,9 @@ 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].
-- 
2.26.2

openSUSE Build Service is sponsored by