File 0658-ssh-replace-size-1-by-xxx_size-1.patch of Package erlang

From 03d73a0e335ae8473e69577f52db43c35a70d972 Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Fri, 3 Feb 2023 09:42:05 +0100
Subject: [PATCH] ssh: replace size/1 by xxx_size/1

The <c>size/1</c> BIF is not optimized by the JIT, and its use can
result in worse types for Dialyzer.

When one knows that the value being tested must be a tuple,
<c>tuple_size/1</c> should always be preferred.

When one knows that the value being tested must be a binary,
<c>byte_size/1</c> should be preferred. However, <c>byte_size/1</c> also
accepts a bitstring (rounding up size to a whole number of bytes), so
one must make sure that the call to <c>byte_size/</c> is preceded by a
call to <c>is_binary/1</c> to ensure that bitstrings are rejected. Note
that the compiler removes redundant calls to <c>is_binary/1</c>, so if
one is not sure whether previous code had made sure that the argument is
a binary, it does not harm to add an <c>is_binary/1</c> test immediately
before the call to <c>byte_size/1</c>.
---
 lib/ssh/src/ssh.hrl                    |  2 +-
 lib/ssh/src/ssh_agent.erl              |  2 +-
 lib/ssh/src/ssh_bits.erl               | 10 +++----
 lib/ssh/src/ssh_client_channel.erl     |  4 +--
 lib/ssh/src/ssh_connection.erl         |  4 +--
 lib/ssh/src/ssh_connection_handler.erl |  2 +-
 lib/ssh/src/ssh_file.erl               |  8 +++---
 lib/ssh/src/ssh_sftp.erl               | 40 +++++++++++++-------------
 lib/ssh/src/ssh_transport.erl          | 24 ++++++++--------
 lib/ssh/src/ssh_xfer.erl               | 16 +++++------
 10 files changed, 56 insertions(+), 56 deletions(-)

diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index c6d1d9d086..08f702f410 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -50,7 +50,7 @@
 -define(UINT16(X),   (X):16/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(DEC_BIN(X,Len),   ?UINT32(Len), X:Len/binary ).
 -define(DEC_INT(I,Len),   ?UINT32(Len), I:Len/big-signed-integer-unit:8 ).
diff --git a/lib/ssh/src/ssh_agent.erl b/lib/ssh/src/ssh_agent.erl
index ffb46df4ea..7ede880737 100644
--- a/lib/ssh/src/ssh_agent.erl
+++ b/lib/ssh/src/ssh_agent.erl
@@ -173,7 +173,7 @@ send(Request, Opts) ->
 %% Message packing
 
 pack(Data) ->
-    <<(size(Data)):32/unsigned-big-integer, Data/binary>>.
+    <<(byte_size(Data)):32/unsigned-big-integer, Data/binary>>.
 
 %% SSH Agent message encoding
 
diff --git a/lib/ssh/src/ssh_bits.erl b/lib/ssh/src/ssh_bits.erl
index 3ce7758447..9a01dbba34 100644
--- a/lib/ssh/src/ssh_bits.erl
+++ b/lib/ssh/src/ssh_bits.erl
@@ -40,20 +40,20 @@ mpint(I) when I>0 ->
     <<B1,V/binary>> = binary:encode_unsigned(I),
     case B1 band 16#80 of
 	16#80 ->
-	    <<(size(V)+2):32/unsigned-big-integer, 0,B1,V/binary >>;
+	    <<(byte_size(V)+2):32/unsigned-big-integer, 0,B1,V/binary >>;
 	_ ->
-	    <<(size(V)+1):32/unsigned-big-integer, B1,V/binary >>
+	    <<(byte_size(V)+1):32/unsigned-big-integer, B1,V/binary >>
     end;
 mpint(N) when N<0 -> 
-    Sxn =  8*size(binary:encode_unsigned(-N)),
+    Sxn =  bit_size(binary:encode_unsigned(-N)),
     Sxn1 = Sxn+8,
     <<W:Sxn1>> = <<1, 0:Sxn>>,
     <<B1,V/binary>> = binary:encode_unsigned(W+N),
     case B1 band 16#80 of
 	16#80 ->
-	    <<(size(V)+1):32/unsigned-big-integer, B1,V/binary >>;
+	    <<(byte_size(V)+1):32/unsigned-big-integer, B1,V/binary >>;
 	_ ->
-	    <<(size(V)+2):32/unsigned-big-integer, 255,B1,V/binary >>
+	    <<(byte_size(V)+2):32/unsigned-big-integer, 255,B1,V/binary >>
     end.
 
 %%%----------------------------------------------------------------
diff --git a/lib/ssh/src/ssh_client_channel.erl b/lib/ssh/src/ssh_client_channel.erl
index e1c7e1a7b5..d7632a1d41 100644
--- a/lib/ssh/src/ssh_client_channel.erl
+++ b/lib/ssh/src/ssh_client_channel.erl
@@ -288,7 +288,7 @@ handle_info(Msg, #state{channel_cb = Module,
 	{stop, ChannelId, ChannelState} ->
             do_the_close(Msg, ChannelId, State#state{channel_state = ChannelState})
     catch
-        error:function_clause when size(Msg) == 3,
+        error:function_clause when tuple_size(Msg) == 3,
                                    element(1,Msg) == 'EXIT' ->
             do_the_close(Msg, State#state.channel_id, State)
     end.
@@ -390,7 +390,7 @@ handle_cb_result({stop, Reason, ChannelState}, State) ->
 
 adjust_window({ssh_cm, ConnectionManager,
 	       {data, ChannelId, _, Data}}) ->
-    ssh_connection:adjust_window(ConnectionManager, ChannelId, size(Data));
+    ssh_connection:adjust_window(ConnectionManager, ChannelId, byte_size(Data));
 adjust_window(_) ->
     ok.
     
diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl
index 4d7ec91a49..9961966e9d 100644
--- a/lib/ssh/src/ssh_connection.erl
+++ b/lib/ssh/src/ssh_connection.erl
@@ -1200,7 +1200,7 @@ get_window(#channel{send_buf = Buffer,
 		   } = Channel, Acc0) ->
     case queue:out(Buffer) of
 	{{value, {_, Data} = Msg}, NewBuffer} ->
-	    case handle_send_window(Msg, size(Data), PacketSize, WindowSize0, Acc0) of		
+	    case handle_send_window(Msg, byte_size(Data), PacketSize, WindowSize0, Acc0) of
 		{WindowSize, Acc, {_, <<>>}} ->
 		    {lists:reverse(Acc), Channel#channel{send_window_size = WindowSize,
 							 send_buf = NewBuffer}};
@@ -1520,7 +1520,7 @@ handle_cli_msg(C0, ChId, Reply0) ->
 channel_data_reply_msg(ChannelId, Connection, DataType, Data) ->
     case ssh_client_channel:cache_lookup(Connection#connection.channel_cache, ChannelId) of
 	#channel{recv_window_size = Size} = Channel ->
-	    WantedSize = Size - size(Data),
+	    WantedSize = Size - byte_size(Data),
 	    ssh_client_channel:cache_update(Connection#connection.channel_cache, 
                                      Channel#channel{recv_window_size = WantedSize}),
             reply_msg(Channel, Connection, {data, ChannelId, DataType, Data});
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 7c07c464e3..ff6eb4b7e4 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -1189,7 +1189,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
 %%%==== 
 handle_event(internal, prepare_next_packet, _StateName, D) ->
     Enough =  erlang:max(8, D#data.ssh_params#ssh.decrypt_block_size),
-    case size(D#data.encrypted_data_buffer) of
+    case byte_size(D#data.encrypted_data_buffer) of
 	Sz when Sz >= Enough ->
 	    self() ! {D#data.transport_protocol, D#data.socket, <<>>};
 	_ ->
diff --git a/lib/ssh/src/ssh_file.erl b/lib/ssh/src/ssh_file.erl
index 056a2068b8..10249d8488 100644
--- a/lib/ssh/src/ssh_file.erl
+++ b/lib/ssh/src/ssh_file.erl
@@ -289,7 +289,7 @@ decode(Bin, auth_keys) when is_binary(Bin) ->
                     [ [[] | binary:split(L,<<" ">>,[global,trim_all])] ];
                 {Pos,Len} when is_integer(Pos), is_integer(Len) ->
                     [ [binary:split(binary:part(L,0,Pos-1), <<",">>,[global,trim_all]) |
-                       binary:split(binary:part(L,Pos,size(L)-Pos), <<" ">>, [global,trim_all])]
+                       binary:split(binary:part(L,Pos,byte_size(L)-Pos), <<" ">>, [global,trim_all])]
                     ]
             end
     ];
@@ -730,12 +730,12 @@ pos_match(H, P) ->
 
         {[Hh], [Ph,<<"*">>]} ->
             %% host [host]:*
-            Sz = size(Hh),
+            Sz = byte_size(Hh),
             Ph == <<"[", Hh:Sz/binary, "]">>;
 
         {[Hh], [Ph,<<"22">>]} ->
             %% host [host]:22
-            Sz = size(Hh),
+            Sz = byte_size(Hh),
             Ph == <<"[", Hh:Sz/binary, "]">>;
 
         _ ->
@@ -1145,7 +1145,7 @@ openssh_key_v1_encode(KeyPairs) ->
                      CheckInt/binary,
                      (openssh_key_v1_encode_priv_keys_cmnts(KeyPairs))/binary>>,
     UnEncrypted = <<UnEncrypted0/binary,
-                    (pad(size(UnEncrypted0), BlockSize))/binary>>,
+                    (pad(byte_size(UnEncrypted0), BlockSize))/binary>>,
     Encrypted = encrypt_openssh_key_v1(UnEncrypted,  KdfName, KdfOptions, CipherName, ignore),
     <<"openssh-key-v1",0,
       ?STRING(CipherName),
diff --git a/lib/ssh/src/ssh_sftp.erl b/lib/ssh/src/ssh_sftp.erl
index 9d912e2a6c..748f767cbe 100644
--- a/lib/ssh/src/ssh_sftp.erl
+++ b/lib/ssh/src/ssh_sftp.erl
@@ -58,9 +58,9 @@
 -record(state,
 	{
 	  xf,
-	  rep_buf = <<>>,
+	  rep_buf = <<>> :: binary(),
 	  req_id,
-	  req_list = [],  %% {ReqId, Fun}
+	  req_list = [], %% {ReqId, Fun}
 	  inf,   %% list of fileinf,
 	  opts
 	 }).
@@ -75,14 +75,14 @@
 
 -record(bufinf,
 	{
-	  mode,			 % read | write  (=from or to buffer by user)
-	  crypto_state,
+	  mode                  :: read | write, % read | write  (=from or to buffer by user)
+	  crypto_state          :: term() | undefined,
 	  crypto_fun,            % For encode or decode depending on the mode field
-	  size = 0,		 % # bytes "before" the current buffer for the position call
+	  size = 0              :: non_neg_integer() | undefined, % # bytes "before" the current buffer for the position call
 
-	  chunksize,		 % The size of the chunks to be sent or received
-	  enc_text_buf = <<>>,	 % Encrypted text
-	  plain_text_buf = <<>>	 % Decrypted text
+	  chunksize             :: non_neg_integer() | undefined, % The size of the chunks to be sent or received
+	  enc_text_buf = <<>>   :: binary() | undefined,          % Encrypted text
+	  plain_text_buf = <<>> :: binary() | undefined           % Decrypted text
 	}).
 
 -define(FILEOP_TIMEOUT, infinity).
@@ -816,7 +816,7 @@ write_file(Pid, Name, Bin, FileOpTimeout) ->
     case open(Pid, Name, [write, binary], FileOpTimeout) of
 	{ok, Handle} ->
 	    {ok,{_Window,Packet}} = send_window(Pid, FileOpTimeout),
-	    Res = write_file_loop(Pid, Handle, 0, Bin, size(Bin), Packet,
+	    Res = write_file_loop(Pid, Handle, 0, Bin, byte_size(Bin), Packet,
 				  FileOpTimeout),
 	    close(Pid, Handle, FileOpTimeout),
 	    Res;
@@ -1017,7 +1017,7 @@ do_handle_call({pwrite,Async,Handle,At,Data0}, From, State) ->
 	{ok,Offset} ->
 	    Data = to_bin(Data0),
 	    ReqID = State#state.req_id,
-	    Size = size(Data),
+	    Size = byte_size(Data),
 	    ssh_xfer:write(?XF(State),ReqID,Handle,Offset,Data),
 	    State1 = update_size(Handle, Offset+Size, State),
 	    make_reply(ReqID, Async, From, State1);
@@ -1030,7 +1030,7 @@ do_handle_call({write,Async,Handle,Data0}, From, State) ->
 	{ok,Offset} ->
 	    Data = to_bin(Data0),
 	    ReqID = State#state.req_id,
-	    Size = size(Data),
+	    Size = byte_size(Data),
 	    ssh_xfer:write(?XF(State),ReqID,Handle,Offset,Data),
 	    State1 = update_offset(Handle, Offset+Size, State),
 	    make_reply(ReqID, Async, From, State1);
@@ -1640,7 +1640,7 @@ read_repeat(Pid, Handle, Len, FileOpTimeout) ->
 read_rpt(Pid, Handle, WantedLen, PacketSz, FileOpTimeout, Acc) when WantedLen > 0 ->
     case read(Pid, Handle, min(WantedLen,PacketSz), FileOpTimeout) of
 	{ok, Data}  ->
-	    read_rpt(Pid, Handle, WantedLen-size(Data), PacketSz, FileOpTimeout, <<Acc/binary, Data/binary>>);
+	    read_rpt(Pid, Handle, WantedLen-byte_size(Data), PacketSz, FileOpTimeout, <<Acc/binary, Data/binary>>);
 	eof ->
 	    {ok, Acc};
 	Error ->
@@ -1654,7 +1654,7 @@ write_to_remote_tar(_Pid, _SftpHandle, <<>>, _FileOpTimeout) ->
     ok;
 write_to_remote_tar(Pid, SftpHandle, Bin, FileOpTimeout) ->
     {ok,{_Window,Packet}} = send_window(Pid, FileOpTimeout),
-    write_file_loop(Pid, SftpHandle, 0, Bin, size(Bin), Packet, FileOpTimeout).
+    write_file_loop(Pid, SftpHandle, 0, Bin, byte_size(Bin), Packet, FileOpTimeout).
 
 position_buf(Pid, SftpHandle, BufHandle, Pos, FileOpTimeout) ->
     {ok,#bufinf{mode = Mode,
@@ -1662,7 +1662,7 @@ position_buf(Pid, SftpHandle, BufHandle, Pos, FileOpTimeout) ->
 		size = Size}} = call(Pid, {get_bufinf,BufHandle}, FileOpTimeout),
     case Pos of
 	{cur,0} when Mode==write ->
-	    {ok,Size+size(Buf0)};
+	    {ok,Size+byte_size(Buf0)};
 
 	{cur,0} when Mode==read ->
 	    {ok,Size};
@@ -1707,7 +1707,7 @@ read_buf(Pid, SftpHandle, BufHandle, WantedLen, FileOpTimeout) ->
 do_the_read_buf(_Pid, _SftpHandle, WantedLen, _Packet, _FileOpTimeout,
 		B=#bufinf{plain_text_buf=PlainBuf0,
 			  size = Size})
-    when size(PlainBuf0) >= WantedLen ->
+    when byte_size(PlainBuf0) >= WantedLen ->
     %% We already have the wanted number of bytes decoded and ready!
     <<ResultBin:WantedLen/binary, PlainBuf/binary>> = PlainBuf0,
     {ok,ResultBin,B#bufinf{plain_text_buf=PlainBuf,
@@ -1718,7 +1718,7 @@ do_the_read_buf(Pid, SftpHandle, WantedLen, Packet, FileOpTimeout,
 			   enc_text_buf = EncBuf0,
 			   chunksize = undefined
 			  })
-  when size(EncBuf0) > 0 ->
+  when byte_size(EncBuf0) > 0 ->
     %% We have (at least) one decodable byte waiting for decoding.
     {ok,DecodedBin,B} = apply_crypto(EncBuf0, B0),
     do_the_read_buf(Pid, SftpHandle, WantedLen, Packet, FileOpTimeout,
@@ -1731,7 +1731,7 @@ do_the_read_buf(Pid, SftpHandle, WantedLen, Packet, FileOpTimeout,
 			   enc_text_buf = EncBuf0,
 			   chunksize = ChunkSize0
 			  })
-  when size(EncBuf0) >= ChunkSize0 ->
+  when byte_size(EncBuf0) >= ChunkSize0 ->
     %% We have (at least) one chunk of decodable bytes waiting for decoding.
     <<ToDecode:ChunkSize0/binary, EncBuf/binary>> = EncBuf0,
     {ok,DecodedBin,B} = apply_crypto(ToDecode, B0),
@@ -1768,7 +1768,7 @@ write_buf(Pid, SftpHandle, BufHandle, PlainBin, FileOpTimeout) ->
 do_the_write_buf(Pid, SftpHandle, Packet, FileOpTimeout,
 		 B=#bufinf{enc_text_buf = EncBuf0,
 			   size = Size})
-  when size(EncBuf0) >= Packet ->
+  when byte_size(EncBuf0) >= Packet ->
     <<BinToWrite:Packet/binary, EncBuf/binary>> = EncBuf0,
     case write(Pid, SftpHandle, BinToWrite, FileOpTimeout) of
 	ok ->
@@ -1783,7 +1783,7 @@ do_the_write_buf(Pid, SftpHandle, Packet, FileOpTimeout,
 		 B0=#bufinf{plain_text_buf = PlainBuf0,
 			    enc_text_buf = EncBuf0,
 			    chunksize = undefined})
-  when size(PlainBuf0) > 0 ->
+  when byte_size(PlainBuf0) > 0 ->
      {ok,EncodedBin,B} = apply_crypto(PlainBuf0, B0),
      do_the_write_buf(Pid, SftpHandle, Packet, FileOpTimeout,
 		     B#bufinf{plain_text_buf = <<>>,
@@ -1794,7 +1794,7 @@ do_the_write_buf(Pid, SftpHandle, Packet, FileOpTimeout,
 			    enc_text_buf = EncBuf0,
 			    chunksize = ChunkSize0
 			   })
-  when size(PlainBuf0) >= ChunkSize0 ->
+  when byte_size(PlainBuf0) >= ChunkSize0 ->
     <<ToEncode:ChunkSize0/binary, PlainBuf/binary>> = PlainBuf0,
     {ok,EncodedBin,B} = apply_crypto(ToEncode, B0),
     do_the_write_buf(Pid, SftpHandle, Packet, FileOpTimeout,
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index 44187cbc72..f74463e1b2 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -1310,9 +1310,9 @@ pack(common, rfc4253, PlainText, DeltaLenTst,
      #ssh{send_sequence = SeqNum,
           send_mac = MacAlg,
           send_mac_key = MacKey} = Ssh0) ->
-    PadLen = padding_length(4+1+size(PlainText), Ssh0),
+    PadLen = padding_length(4+1+byte_size(PlainText), Ssh0),
     Pad =  ssh_bits:random(PadLen),
-    TextLen = 1 + size(PlainText) + PadLen + DeltaLenTst,
+    TextLen = 1 + byte_size(PlainText) + PadLen + DeltaLenTst,
     PlainPkt = <<?UINT32(TextLen),?BYTE(PadLen), PlainText/binary, Pad/binary>>,
     {Ssh1, CipherPkt} = encrypt(Ssh0, PlainPkt),
     MAC0 = mac(MacAlg, MacKey, SeqNum, PlainPkt),
@@ -1323,9 +1323,9 @@ pack(common, enc_then_mac, PlainText, DeltaLenTst,
      #ssh{send_sequence = SeqNum,
           send_mac = MacAlg,
           send_mac_key = MacKey} = Ssh0) ->
-    PadLen = padding_length(1+size(PlainText), Ssh0),
+    PadLen = padding_length(1+byte_size(PlainText), Ssh0),
     Pad =  ssh_bits:random(PadLen),
-    PlainLen = 1 + size(PlainText) + PadLen + DeltaLenTst,
+    PlainLen = 1 + byte_size(PlainText) + PadLen + DeltaLenTst,
     PlainPkt = <<?BYTE(PadLen), PlainText/binary, Pad/binary>>,
     {Ssh1, CipherPkt} = encrypt(Ssh0, PlainPkt),
     EncPacketPkt = <<?UINT32(PlainLen), CipherPkt/binary>>,
@@ -1333,9 +1333,9 @@ pack(common, enc_then_mac, PlainText, DeltaLenTst,
     {<<?UINT32(PlainLen), CipherPkt/binary, MAC0/binary>>, Ssh1};
 
 pack(aead, _, PlainText, DeltaLenTst, Ssh0) ->
-    PadLen = padding_length(1+size(PlainText), Ssh0),
+    PadLen = padding_length(1+byte_size(PlainText), Ssh0),
     Pad =  ssh_bits:random(PadLen),
-    PlainLen = 1 + size(PlainText) + PadLen + DeltaLenTst,
+    PlainLen = 1 + byte_size(PlainText) + PadLen + DeltaLenTst,
     PlainPkt = <<?BYTE(PadLen), PlainText/binary, Pad/binary>>,
     {Ssh1, {CipherPkt,MAC0}} = encrypt(Ssh0, <<?UINT32(PlainLen),PlainPkt/binary>>),
     {<<CipherPkt/binary,MAC0/binary>>, Ssh1}.
@@ -1362,7 +1362,7 @@ handle_packet_part(<<>>, Encrypted0, AEAD0, undefined, #ssh{decrypt = CryptoAlg,
     end;
 
 handle_packet_part(DecryptedPfx, EncryptedBuffer, AEAD, TotalNeeded, Ssh0) 
-  when (size(DecryptedPfx)+size(EncryptedBuffer)) < TotalNeeded ->
+  when (byte_size(DecryptedPfx)+byte_size(EncryptedBuffer)) < TotalNeeded ->
     %% need more bytes to finalize the packet
     {get_more, DecryptedPfx, EncryptedBuffer, AEAD, TotalNeeded, Ssh0};
 
@@ -1381,7 +1381,7 @@ handle_packet_part(DecryptedPfx, EncryptedBuffer, AEAD, TotalNeeded, #ssh{decryp
 %%%----------------
 unpack(common, rfc4253, DecryptedPfx, EncryptedBuffer, _AEAD, TotalNeeded,
        #ssh{recv_mac_size = MacSize} = Ssh0) ->
-    MoreNeeded = TotalNeeded - size(DecryptedPfx) - MacSize,
+    MoreNeeded = TotalNeeded - byte_size(DecryptedPfx) - MacSize,
     <<EncryptedSfx:MoreNeeded/binary, Mac:MacSize/binary, NextPacketBytes/binary>> = EncryptedBuffer,
     {Ssh1, DecryptedSfx} = decrypt(Ssh0, EncryptedSfx),
     PlainPkt = <<DecryptedPfx/binary, DecryptedSfx/binary>>,
@@ -1398,7 +1398,7 @@ unpack(common, enc_then_mac, <<?UINT32(PlainLen)>>, EncryptedBuffer, _AEAD, _Tot
     case is_valid_mac(MAC0, <<?UINT32(PlainLen),Payload/binary>>, Ssh0) of
         true ->
             {Ssh1, <<?BYTE(PaddingLen), PlainRest/binary>>} = decrypt(Ssh0, Payload),
-            CompressedPlainTextLen = size(PlainRest) - PaddingLen,
+            CompressedPlainTextLen = byte_size(PlainRest) - PaddingLen,
             <<CompressedPlainText:CompressedPlainTextLen/binary, _Padding/binary>> = PlainRest,
             {ok, CompressedPlainText, NextPacketBytes, Ssh1};
         false ->
@@ -1408,7 +1408,7 @@ unpack(common, enc_then_mac, <<?UINT32(PlainLen)>>, EncryptedBuffer, _AEAD, _Tot
 unpack(aead, _, DecryptedPfx, EncryptedBuffer, AEAD, TotalNeeded, 
        #ssh{recv_mac_size = MacSize} = Ssh0) ->
     %% enough bytes to decode the packet.
-    MoreNeeded = TotalNeeded - size(DecryptedPfx) - MacSize,
+    MoreNeeded = TotalNeeded - byte_size(DecryptedPfx) - MacSize,
     <<EncryptedSfx:MoreNeeded/binary, Mac:MacSize/binary, NextPacketBytes/binary>> = EncryptedBuffer,
     case decrypt(Ssh0, {AEAD,EncryptedSfx,Mac}) of
         {Ssh1, error} ->
@@ -1420,7 +1420,7 @@ unpack(aead, _, DecryptedPfx, EncryptedBuffer, AEAD, TotalNeeded,
 
 %%%----------------------------------------------------------------
 get_length(common, rfc4253, EncryptedBuffer, #ssh{decrypt_block_size = BlockSize} = Ssh0) ->
-    case size(EncryptedBuffer) >= erlang:max(8, BlockSize) of
+    case byte_size(EncryptedBuffer) >= erlang:max(8, BlockSize) of
 	true ->
 	    <<EncBlock:BlockSize/binary, EncryptedRest/binary>> = EncryptedBuffer,
 	    {Ssh, 
@@ -1440,7 +1440,7 @@ get_length(common, enc_then_mac, EncryptedBuffer, Ssh) ->
     end;
 
 get_length(aead, _, EncryptedBuffer, Ssh) ->
-    case {size(EncryptedBuffer) >= 4, Ssh#ssh.decrypt} of
+    case {byte_size(EncryptedBuffer) >= 4, Ssh#ssh.decrypt} of
        {true, 'chacha20-poly1305@openssh.com'} ->
             <<EncryptedLen:4/binary, EncryptedRest/binary>> = EncryptedBuffer,
             {Ssh1,  PacketLenBin} = decrypt(Ssh, {length,EncryptedLen}),
diff --git a/lib/ssh/src/ssh_xfer.erl b/lib/ssh/src/ssh_xfer.erl
index 212798f2d7..df5a8b2eec 100644
--- a/lib/ssh/src/ssh_xfer.erl
+++ b/lib/ssh/src/ssh_xfer.erl
@@ -242,7 +242,7 @@ xf_request(XF, Op, Arg) ->
 	       is_list(Arg) ->
 		   ?to_binary(Arg)
 	   end,
-    Size = 1+size(Data),
+    Size = 1+byte_size(Data),
     ssh_connection:send(CM, Channel, [<<?UINT32(Size), Op, Data/binary>>]).
 
 xf_send_reply(#ssh_xfer{cm = CM, channel = Channel}, Op, Arg) ->    
@@ -252,7 +252,7 @@ xf_send_reply(#ssh_xfer{cm = CM, channel = Channel}, Op, Arg) ->
 	       is_list(Arg) ->
 		   ?to_binary(Arg)
 	   end,
-    Size = 1 + size(Data),
+    Size = 1 + byte_size(Data),
     ssh_connection:send(CM, Channel, [<<?UINT32(Size), Op, Data/binary>>]).
 
 xf_send_name(XF, ReqId, Name, Attr) ->
@@ -290,7 +290,7 @@ xf_send_status(#ssh_xfer{cm = CM, channel = Channel},
     LangTag = "en",
     ELen = length(ErrorMsg),
     TLen = 2, %% length(LangTag),
-    Size = 1 + 4 + 4 + 4+ELen + 4+TLen + size(Data),
+    Size = 1 + 4 + 4 + 4+ELen + 4+TLen + byte_size(Data),
     ToSend = [<<?UINT32(Size), ?SSH_FXP_STATUS, ?UINT32(ReqId),
 	       ?UINT32(ErrorCode)>>,
 	      <<?UINT32(ELen)>>, ErrorMsg,
@@ -300,13 +300,13 @@ xf_send_status(#ssh_xfer{cm = CM, channel = Channel},
 
 xf_send_attr(#ssh_xfer{cm = CM, channel = Channel, vsn = Vsn}, ReqId, Attr) ->
     EncAttr = encode_ATTR(Vsn, Attr),
-    ALen = size(EncAttr),
+    ALen = byte_size(EncAttr),
     Size = 1 + 4 + ALen,
     ToSend = [<<?UINT32(Size), ?SSH_FXP_ATTRS, ?UINT32(ReqId)>>, EncAttr],
     ssh_connection:send(CM, Channel, ToSend).
 
 xf_send_data(#ssh_xfer{cm = CM, channel = Channel}, ReqId, Data) ->
-    DLen = size(Data),
+    DLen = byte_size(Data),
     Size = 1 + 4 + 4+DLen,
     ToSend = [<<?UINT32(Size), ?SSH_FXP_DATA, ?UINT32(ReqId), ?UINT32(DLen)>>,
 	      Data],
@@ -815,21 +815,21 @@ encode_name(Vsn, {{NameUC,LongNameUC},Attr}, Len) when Vsn =< 3 ->
 	LongName = binary_to_list(unicode:characters_to_binary(LongNameUC)),
     LNLen = length(LongName),
 	EncAttr = encode_ATTR(Vsn, Attr),
-    ALen = size(EncAttr),
+    ALen = byte_size(EncAttr),
     NewLen = Len + NLen + LNLen + 4 + 4 + ALen,
     {[<<?UINT32(NLen)>>, Name, <<?UINT32(LNLen)>>, LongName, EncAttr], NewLen};
 encode_name(Vsn, {NameUC,Attr}, Len) when Vsn =< 3 ->
     Name = binary_to_list(unicode:characters_to_binary(NameUC)),
     NLen = length(Name),
     EncAttr = encode_ATTR(Vsn, Attr),
-    ALen = size(EncAttr),
+    ALen = byte_size(EncAttr),
     NewLen = Len + NLen*2 + 4 + 4 + ALen,
     {[<<?UINT32(NLen)>>, Name, <<?UINT32(NLen)>>, Name, EncAttr], NewLen};
 encode_name(Vsn, {NameUC,Attr}, Len) when Vsn >= 4 ->
     Name = binary_to_list(unicode:characters_to_binary(NameUC)),
     NLen = length(Name),
     EncAttr = encode_ATTR(Vsn, Attr),
-    ALen = size(EncAttr),
+    ALen = byte_size(EncAttr),
     {[<<?UINT32(NLen)>>, Name, EncAttr],
      Len + 4 + NLen + ALen}.
 
-- 
2.35.3

openSUSE Build Service is sponsored by