File 0626-Replace-size-1-with-either-tuple_size-1-or-byte_size.patch of Package erlang
From 11b56edc258a4d42cfb3a595ebd8592cf4afea12 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 16 Jan 2023 06:56:59 +0100
Subject: [PATCH] Replace size/1 with either tuple_size/1 or byte_size/1
The `size/1` 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,
`tuple_size/1` should always be preferred.
When one knows that the value being tested must be a binary,
`byte_size/1` should be preferred. However, `byte_size/1` also accepts
a bitstring (rounding up size to a whole number of bytes), so one must
make sure that the call to `byte_size/1` is preceded by a call to
`is_binary/1` to ensure that bitstrings are rejected. Note that the
compiler removes redundant calls to `is_binary/1`, 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 `is_binary/1` test immediately
before the call to `byte_size/1`.
---
lib/common_test/src/ct_framework.erl | 2 +-
lib/common_test/src/ct_groups.erl | 7 +++----
lib/common_test/src/ct_netconfc.erl | 18 +++++++++---------
lib/common_test/src/ct_ssh.erl | 4 ++--
lib/common_test/src/ct_testspec.erl | 4 ++--
lib/common_test/src/ct_util.erl | 2 +-
lib/common_test/test/test_server_SUITE.erl | 2 +-
7 files changed, 19 insertions(+), 20 deletions(-)
diff --git a/lib/common_test/src/ct_framework.erl b/lib/common_test/src/ct_framework.erl
index 765a90103c..ed9028b99f 100644
--- a/lib/common_test/src/ct_framework.erl
+++ b/lib/common_test/src/ct_framework.erl
@@ -443,7 +443,7 @@ get_suite_name(Mod, _) ->
%% Check that alias names are not already in use
check_for_clashes(TCInfo, [CurrGrInfo|Path], SuiteInfo) ->
ReqNames = fun(Info) -> [element(2,R) || R <- Info,
- size(R) == 3,
+ tuple_size(R) == 3,
require == element(1,R)]
end,
ExistingNames = lists:flatten([ReqNames(L) || L <- [SuiteInfo|Path]]),
diff --git a/lib/common_test/src/ct_groups.erl b/lib/common_test/src/ct_groups.erl
index ee851d5103..db610d6e4c 100644
--- a/lib/common_test/src/ct_groups.erl
+++ b/lib/common_test/src/ct_groups.erl
@@ -191,8 +191,8 @@ find(Mod, GrNames, all, [{testcase,TC,[Prop]} | Gs], Known,
%% Check if test case should be saved
find(Mod, GrNames, TCs, [TC | Gs], Known, Defs, FindAll)
when is_atom(TC) orelse
- ((size(TC) == 3) andalso (element(1,TC) == testcase)) orelse
- ((size(TC) == 2) and (element(1,TC) /= group)) ->
+ ((tuple_size(TC) == 3) andalso (element(1,TC) == testcase)) orelse
+ ((tuple_size(TC) == 2) andalso (element(1,TC) /= group)) ->
Case =
case TC of
_ when is_atom(TC) ->
@@ -333,8 +333,7 @@ modify_tc_list1(GrSpecTs, TSCs) ->
false -> []
end
end;
- (Test) when is_tuple(Test),
- (size(Test) > 2) ->
+ (Test) when tuple_size(Test) > 2 ->
[Test];
(Test={group,_}) ->
[Test];
diff --git a/lib/common_test/src/ct_netconfc.erl b/lib/common_test/src/ct_netconfc.erl
index 07f6cc1b8f..bc009b20eb 100644
--- a/lib/common_test/src/ct_netconfc.erl
+++ b/lib/common_test/src/ct_netconfc.erl
@@ -1023,8 +1023,8 @@ handle_msg({get_event_streams=Op,Streams,Timeout}, From, State) ->
SimpleXml = encode_rpc_operation(get,[Filter]),
do_send_rpc(Op, SimpleXml, Timeout, From, State).
-handle_msg({ssh_cm, CM, {data, Ch, _Type, Data}}, State) ->
- ssh_connection:adjust_window(CM,Ch,size(Data)),
+handle_msg({ssh_cm, CM, {data, Ch, _Type, Data}}, State) when is_binary(Data) ->
+ ssh_connection:adjust_window(CM,Ch,byte_size(Data)),
log(State#state.connection, recv, Data),
handle_data(Data, State);
@@ -1395,8 +1395,8 @@ frame(Bin) ->
chunk(<<>>) ->
[];
-chunk(Bin) ->
- Sz = min(rand:uniform(1024), size(Bin)),
+chunk(Bin) when is_binary(Bin) ->
+ Sz = min(rand:uniform(1024), byte_size(Bin)),
<<B:Sz/binary, Rest/binary>> = Bin,
["\n#", integer_to_list(Sz), $\n, B | chunk(Rest)].
@@ -2081,7 +2081,7 @@ recv(Bin, [Head, Len | Chunks]) -> %% 1.1 chunking
%% 5 characters from the end of the buffered head, since this binary
%% has already been scanned.
recv(Bin, Head) when is_binary(Head) -> %% 1.0 framing
- frame(<<Head/binary, Bin/binary>>, max(0, size(Head) - 5)).
+ frame(<<Head/binary, Bin/binary>>, max(0, byte_size(Head) - 5)).
%% frame/2
%%
@@ -2090,8 +2090,8 @@ recv(Bin, Head) when is_binary(Head) -> %% 1.0 framing
%% is unambiguous: the high-order bit of every byte of a multi-byte
%% UTF character is 1, while the end-of-message sequence is ASCII.
-frame(Bin, Start) ->
- Sz = size(Bin),
+frame(Bin, Start) when is_binary(Bin) ->
+ Sz = byte_size(Bin),
Scope = {Start, Sz - Start},
case binary:match(Bin, pattern(), [{scope, Scope}]) of
{Len, 6} ->
@@ -2150,7 +2150,7 @@ chunk(Bin, [Sz | Chunks] = L, 0) ->
%% ... or a header.
chunk(Bin, Chunks, Len)
- when size(Bin) < 4 ->
+ when byte_size(Bin) < 4 ->
[Bin, 3 = Len | Chunks];
%% End of chunks.
@@ -2189,7 +2189,7 @@ chunk(<<"\n#", Bin:11/binary, _/binary>>, _, _) ->
{error, {"chunk-size too long", Bin}}; %% 32-bits = max 10 digits
chunk(<<"\n#", _/binary>> = Bin, Chunks, _) ->
- [Bin, size(Bin) | Chunks];
+ [Bin, byte_size(Bin) | Chunks];
chunk(Bin, Chunks, 3 = Len) ->
case drop(Bin) of
diff --git a/lib/common_test/src/ct_ssh.erl b/lib/common_test/src/ct_ssh.erl
index 79ab122452..6446bc840b 100644
--- a/lib/common_test/src/ct_ssh.erl
+++ b/lib/common_test/src/ct_ssh.erl
@@ -738,8 +738,8 @@ do_recv_response(SSH, Chn, Data, End, Timeout) ->
debug("CLSD~n~p ~p", [SSH,Chn]),
{ok,Data};
- {ssh_cm, SSH, {data,Chn,_,NewData}} ->
- ssh_connection:adjust_window(SSH, Chn, size(NewData)),
+ {ssh_cm, SSH, {data,Chn,_,NewData}} when is_binary(NewData) ->
+ ssh_connection:adjust_window(SSH, Chn, byte_size(NewData)),
debug("RECVD~n~tp", [binary_to_list(NewData)]),
DataAcc = Data ++ binary_to_list(NewData),
if is_function(End) ->
diff --git a/lib/common_test/src/ct_testspec.erl b/lib/common_test/src/ct_testspec.erl
index d9cefc77cd..ae4565fd13 100644
--- a/lib/common_test/src/ct_testspec.erl
+++ b/lib/common_test/src/ct_testspec.erl
@@ -1079,7 +1079,7 @@ add_tests([],Spec) -> % done
%% have added something of his/her own, which we'll let pass if relaxed
%% mode is enabled.
check_term(Term) when is_tuple(Term) ->
- Size = size(Term),
+ Size = tuple_size(Term),
[Name|_] = tuple_to_list(Term),
Valid = valid_terms(),
case lists:member({Name,Size},Valid) of
@@ -1093,7 +1093,7 @@ check_term(Term) when is_tuple(Term) ->
case get(relaxed) of
true ->
%% warn if name resembles a CT term
- case resembles_ct_term(Name,size(Term)) of
+ case resembles_ct_term(Name,tuple_size(Term)) of
true ->
io:format("~nSuspicious term, "
"please check:~n"
diff --git a/lib/common_test/src/ct_util.erl b/lib/common_test/src/ct_util.erl
index 3e711708c0..21fdb9ede0 100644
--- a/lib/common_test/src/ct_util.erl
+++ b/lib/common_test/src/ct_util.erl
@@ -786,7 +786,7 @@ listenv(Telnet) ->
%%% Equivalent to ct:parse_table/1
parse_table(Data) ->
{Heading, Rest} = get_headings(Data),
- Lines = parse_row(Rest,[],size(Heading)),
+ Lines = parse_row(Rest,[],tuple_size(Heading)),
{Heading,Lines}.
get_headings(["|" ++ Headings | Rest]) ->
diff --git a/lib/common_test/test/test_server_SUITE.erl b/lib/common_test/test/test_server_SUITE.erl
index 37c7731404..915ea90c94 100644
--- a/lib/common_test/test/test_server_SUITE.erl
+++ b/lib/common_test/test/test_server_SUITE.erl
@@ -283,7 +283,7 @@ get_latest_run_dir(Dir) ->
Dir
end.
-l(X) when is_binary(X) -> size(X);
+l(X) when is_binary(X) -> byte_size(X);
l(X) when is_list(X) -> length(X).
get_latest_dir([H|T],Latest) when H>Latest ->
--
2.35.3