File 5441-mnesia-replace-size-1-by-xxx_size-1.patch of Package erlang

From 85608433739b0578f56de748b18c0840d96a8ef9 Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Thu, 2 Feb 2023 12:34:06 +0100
Subject: [PATCH] mnesia: 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/mnesia/src/mnesia_index.erl     | 2 +-
 lib/mnesia/src/mnesia_lib.erl       | 2 +-
 lib/mnesia/src/mnesia_loader.erl    | 2 +-
 lib/mnesia/src/mnesia_schema.erl    | 6 +++---
 lib/mnesia/src/mnesia_snmp_hook.erl | 4 ++--
 5 files changed, 8 insertions(+), 8 deletions(-)

diff --git a/lib/mnesia/src/mnesia_index.erl b/lib/mnesia/src/mnesia_index.erl
index d9f7da8eda..a6c2229645 100644
--- a/lib/mnesia/src/mnesia_index.erl
+++ b/lib/mnesia/src/mnesia_index.erl
@@ -332,7 +332,7 @@ init_disc_index(Tab, disc_only_copies, [{Pos,_Pref} | Tail]) ->
     Storage = disc_only_copies,
     Key = mnesia_lib:db_first(Storage, Tab),
     Recs = mnesia_lib:db_get(Storage, Tab, Key),
-    BinSize = size(term_to_binary(Recs)),
+    BinSize = byte_size(term_to_binary(Recs)),
     KeysPerChunk = (4000 div BinSize) + 1,
     Init = {start, KeysPerChunk},
     mnesia_lib:db_fixtable(Storage, Tab, true),
diff --git a/lib/mnesia/src/mnesia_lib.erl b/lib/mnesia/src/mnesia_lib.erl
index 37380fba87..50a004aab0 100644
--- a/lib/mnesia/src/mnesia_lib.erl
+++ b/lib/mnesia/src/mnesia_lib.erl
@@ -950,7 +950,7 @@ error_desc({error, Reason}) ->
     error_desc(Reason);
 error_desc({aborted, Reason}) ->
     error_desc(Reason);
-error_desc(Reason) when is_tuple(Reason), size(Reason) > 0 ->
+error_desc(Reason) when tuple_size(Reason) > 0 ->
     setelement(1, Reason, error_desc(element(1, Reason)));
 error_desc(Reason) ->
     Reason.
diff --git a/lib/mnesia/src/mnesia_loader.erl b/lib/mnesia/src/mnesia_loader.erl
index 4dea366964..0500cbebdf 100644
--- a/lib/mnesia/src/mnesia_loader.erl
+++ b/lib/mnesia/src/mnesia_loader.erl
@@ -760,7 +760,7 @@ calc_nokeys(Storage, Tab) ->
     %% Calculate #keys per transfer
     Key = mnesia_lib:db_first(Storage, Tab),
     Recs = mnesia_lib:db_get(Storage, Tab, Key),
-    BinSize = size(term_to_binary(Recs)),
+    BinSize = byte_size(term_to_binary(Recs)),
     (max_transfer_size() div BinSize) + 1.
 
 send_table(Pid, Tab, RemoteS, Reason) ->
diff --git a/lib/mnesia/src/mnesia_schema.erl b/lib/mnesia/src/mnesia_schema.erl
index 42c717425e..6e0460f785 100644
--- a/lib/mnesia/src/mnesia_schema.erl
+++ b/lib/mnesia/src/mnesia_schema.erl
@@ -1186,7 +1186,7 @@ assert_correct_cstruct(Cs) when is_record(Cs, cstruct) ->
     verify(true, mnesia_snmp_hook:check_ustruct(Snmp),
 	   {badarg, Tab, {snmp, Snmp}}),
 
-    CheckProp = fun(Prop) when is_tuple(Prop), size(Prop) >= 1 -> ok;
+    CheckProp = fun(Prop) when tuple_size(Prop) >= 1 -> ok;
 		   (Prop) ->
 			mnesia:abort({bad_type, Tab,
 				      {user_properties, [Prop]}})
@@ -2126,7 +2126,7 @@ make_change_table_majority(Tab, Majority) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-write_table_property(Tab, Prop) when is_tuple(Prop), size(Prop) >= 1 ->
+write_table_property(Tab, Prop) when tuple_size(Prop) >= 1 ->
     schema_transaction(fun() -> do_write_table_property(Tab, Prop) end);
 write_table_property(Tab, Prop) ->
     {aborted, {bad_type, Tab, Prop}}.
@@ -2809,7 +2809,7 @@ transform_objs(Fun, Tab, RecName, Key, A, Storage, Type, Acc) ->
 transform_obj(Tab, RecName, Key, Fun, [Obj|Rest], NewArity, Type, Ws, Ds) ->
     NewObj = Fun(Obj),
     if
-        size(NewObj) /= NewArity ->
+        tuple_size(NewObj) /= NewArity ->
             exit({"Bad arity", Obj, NewObj});
 	NewObj == Obj ->
 	    transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, Type, Ws, Ds);
diff --git a/lib/mnesia/src/mnesia_snmp_hook.erl b/lib/mnesia/src/mnesia_snmp_hook.erl
index 93a04d44f8..1c57b44066 100644
--- a/lib/mnesia/src/mnesia_snmp_hook.erl
+++ b/lib/mnesia/src/mnesia_snmp_hook.erl
@@ -124,7 +124,7 @@ key_to_oid(Tab, Key, [{key, Types}]) ->
 key_to_oid_i(Key, integer) when is_integer(Key) -> [Key];
 key_to_oid_i(Key, fix_string) when is_list(Key) -> Key;
 key_to_oid_i(Key, string) when is_list(Key) -> [length(Key) | Key];
-key_to_oid_i(Key, Types) -> keys_to_oid(size(Key), Key, [], Types).
+key_to_oid_i(Key, Types) when is_tuple(Key) -> keys_to_oid(tuple_size(Key), Key, [], Types).
 
 keys_to_oid(0, _Key, Oid, _Types) -> Oid;
 keys_to_oid(N, Key, Oid, Types) ->
@@ -144,7 +144,7 @@ oid_to_key_1(fix_string, Key) -> Key;
 oid_to_key_1(string, [_|Key]) -> Key;
 oid_to_key_1(Tuple, Oid) ->
     try 
-	List = oid_to_key_2(1, size(Tuple), Tuple, Oid),
+	List = oid_to_key_2(1, tuple_size(Tuple), Tuple, Oid),
 	list_to_tuple(List)
     catch 
 	_:_ -> unknown
-- 
2.35.3

openSUSE Build Service is sponsored by