File 0660-tftp-replace-size-1-by-xxx_size-1.patch of Package erlang

From e30b936bcf4b7314acd06c146f0fa09069c72573 Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Fri, 3 Feb 2023 10:54:43 +0100
Subject: [PATCH] tftp: 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/tftp/src/tftp_binary.erl | 10 +++++-----
 lib/tftp/src/tftp_engine.erl | 10 +++++-----
 lib/tftp/src/tftp_file.erl   | 10 +++++-----
 lib/tftp/src/tftp_lib.erl    |  4 ++--
 4 files changed, 17 insertions(+), 17 deletions(-)

diff --git a/lib/tftp/src/tftp_binary.erl b/lib/tftp/src/tftp_binary.erl
index 3438ba235b..c337110ca2 100644
--- a/lib/tftp/src/tftp_binary.erl
+++ b/lib/tftp/src/tftp_binary.erl
@@ -53,7 +53,7 @@ prepare(_Peer, Access, Filename, Mode, SuggestedOptions, Initial) when is_list(I
 				blksize  	 = lookup_blksize(AcceptedOptions),
 				bin      	 = Filename,
 				is_network_ascii = IsNetworkAscii,
-			        count            = size(Filename),
+			        count            = byte_size(Filename),
 				is_native_ascii  = IsNativeAscii},
 	    {ok, AcceptedOptions, State};
 	{ok, IsNetworkAscii, AcceptedOptions} when Access =:= write, Filename =:= binary ->
@@ -115,11 +115,11 @@ open(Peer, Access, Filename, Mode, NegotiatedOptions, State) ->
 read(#read_state{bin = Bin} = State) when is_binary(Bin) ->
     BlkSize = State#read_state.blksize,
     if
-	size(Bin) >= BlkSize ->
+	byte_size(Bin) >= BlkSize ->
 	    <<Block:BlkSize/binary, Bin2/binary>> = Bin,
 	    State2 = State#read_state{bin = Bin2},
 	    {more, Block, State2};
-	size(Bin) < BlkSize ->
+	byte_size(Bin) < BlkSize ->
 	    {last, Bin, State#read_state.count}
     end;
 read(State) ->
@@ -132,7 +132,7 @@ read(State) ->
 %%-------------------------------------------------------------------
 
 write(Bin, #write_state{list = List} = State) when is_binary(Bin), is_list(List) ->
-    Size = size(Bin),
+    Size = byte_size(Bin),
     BlkSize = State#write_state.blksize,
     if
 	Size =:= BlkSize ->
@@ -182,7 +182,7 @@ do_handle_options(Access, Bin, [{Key, Val} | T]) ->
 	"tsize" ->
 	    case Access of
 		read when Val =:= "0", is_binary(Bin) ->
-		    Tsize = integer_to_list(size(Bin)),
+		    Tsize = integer_to_list(byte_size(Bin)),
 		    [{Key, Tsize} | do_handle_options(Access, Bin, T)];
 		_ ->
 		    handle_integer(Access, Bin, Key, Val, T, 0, infinity)
diff --git a/lib/tftp/src/tftp_engine.erl b/lib/tftp/src/tftp_engine.erl
index 811f91b8bd..43ba51f267 100644
--- a/lib/tftp/src/tftp_engine.erl
+++ b/lib/tftp/src/tftp_engine.erl
@@ -1001,7 +1001,7 @@ do_callback(read = Fun, Config, Callback, Req)
     NextBlockNo = Callback#callback.block_no + 1,
     case catch safe_apply(Callback#callback.module, Fun, Args) of
         {more, Bin, NewState} when is_binary(Bin) ->
-            Count = Callback#callback.count + size(Bin),
+            Count = Callback#callback.count + byte_size(Bin),
             Callback2 = Callback#callback{state    = NewState, 
                                           block_no = NextBlockNo,
                                           count    = Count},
@@ -1035,7 +1035,7 @@ do_callback({write = Fun, Bin}, Config, Callback, Req)
     NextBlockNo = Callback#callback.block_no + 1,
     case catch safe_apply(Callback#callback.module, Fun, Args) of
         {more, NewState} ->
-            Count = Callback#callback.count + size(Bin),
+            Count = Callback#callback.count + byte_size(Bin),
             Callback2 = Callback#callback{state    = NewState, 
                                           block_no = NextBlockNo,
                                           count    = Count},
@@ -1112,9 +1112,9 @@ do_callback({abort, Error}, _Config, undefined, _Req) when is_record(Error, tftp
 
 peer_info(#config{udp_host = Host, udp_port = Port}) ->
     if
-        is_tuple(Host), size(Host) =:= 4 ->
+        tuple_size(Host) =:= 4 ->
             {inet, tftp_lib:host_to_string(Host), Port};
-        is_tuple(Host), size(Host) =:= 8 ->
+        tuple_size(Host) =:= 8 ->
             {inet6, tftp_lib:host_to_string(Host), Port};
         true ->
             {undefined, Host, Port}
@@ -1336,7 +1336,7 @@ print_debug_info(#config{debug_level = Level} = Config, Who, Where, Data) ->
     end.
 
 do_print_debug_info(Config, Who, Where, #tftp_msg_data{data = Bin} = Msg) when is_binary(Bin) ->
-    Msg2 = Msg#tftp_msg_data{data = {bytes, size(Bin)}},
+    Msg2 = Msg#tftp_msg_data{data = {bytes, byte_size(Bin)}},
     do_print_debug_info(Config, Who, Where, Msg2);
 do_print_debug_info(Config, Who, Where, #tftp_msg_req{local_filename = Filename} = Msg) when is_binary(Filename) ->
     Msg2 = Msg#tftp_msg_req{local_filename = binary},
diff --git a/lib/tftp/src/tftp_file.erl b/lib/tftp/src/tftp_file.erl
index 152131b3d6..a164b019c2 100644
--- a/lib/tftp/src/tftp_file.erl
+++ b/lib/tftp/src/tftp_file.erl
@@ -211,12 +211,12 @@ file_error(Reason) when is_atom(Reason) ->
 read(#state{access = read} = State) ->
     BlkSize = State#state.blksize,
     case file:read(State#state.fd, BlkSize) of
-	{ok, Bin} when is_binary(Bin), size(Bin) =:= BlkSize ->
-	    Count = State#state.count + size(Bin),
+	{ok, Bin} when is_binary(Bin), byte_size(Bin) =:= BlkSize ->
+	    Count = State#state.count + byte_size(Bin),
 	    {more, Bin, State#state{count = Count}};
-	{ok, Bin} when is_binary(Bin), size(Bin) < BlkSize ->
+	{ok, Bin} when is_binary(Bin), byte_size(Bin) < BlkSize ->
 	    _ = file:close(State#state.fd),
-	    Count = State#state.count + size(Bin),
+	    Count = State#state.count + byte_size(Bin),
 	    {last, Bin, Count};
 	eof ->
 	    {last, <<>>, State#state.count};
@@ -248,7 +248,7 @@ read(State) ->
 %%-------------------------------------------------------------------
 
 write(Bin, #state{access = write} = State) when is_binary(Bin) ->
-    Size = size(Bin),
+    Size = byte_size(Bin),
     BlkSize = State#state.blksize,
     case file:write(State#state.fd, Bin) of
 	ok when Size =:= BlkSize->
diff --git a/lib/tftp/src/tftp_lib.erl b/lib/tftp/src/tftp_lib.erl
index 407a273f58..bc5496f9a0 100644
--- a/lib/tftp/src/tftp_lib.erl
+++ b/lib/tftp/src/tftp_lib.erl
@@ -94,9 +94,9 @@ do_parse_config([{Key, Val} | Tail], Config) when is_record(Config, config) ->
             if
                 is_list(Val) ->
                     do_parse_config(Tail, Config#config{udp_host = Val});
-                is_tuple(Val), size(Val) =:= 4 ->
+                tuple_size(Val) =:= 4 ->
                     do_parse_config(Tail, Config#config{udp_host = Val});
-                is_tuple(Val), size(Val) =:= 8 ->
+                tuple_size(Val) =:= 8 ->
                     do_parse_config(Tail, Config#config{udp_host = Val});
                 true ->
                     exit({badarg, {Key, Val}})
-- 
2.35.3

openSUSE Build Service is sponsored by