File 2811-mnesia-Remove-module-mnesia_registry.patch of Package erlang

From 2d4824677a0d3f5112cb02dc9a2b351d166b2fde Mon Sep 17 00:00:00 2001
From: Johannes Christ <jc@jchri.st>
Date: Tue, 14 Oct 2025 12:30:15 +0200
Subject: [PATCH] mnesia: Remove module mnesia_registry

---
 lib/mnesia/src/mnesia.erl                     |   1 -
 lib/mnesia/src/mnesia_registry.erl            | 309 +-----------------
 lib/mnesia/test/Makefile                      |   1 -
 lib/mnesia/test/mnesia_SUITE.erl              |   5 +-
 lib/mnesia/test/mnesia_evil_coverage_test.erl |  12 -
 lib/mnesia/test/mnesia_registry_test.erl      | 150 ---------
 lib/mnesia/test/mt.erl                        |   1 -
 7 files changed, 3 insertions(+), 476 deletions(-)
 delete mode 100644 lib/mnesia/test/mnesia_registry_test.erl

diff --git a/lib/mnesia/src/mnesia.erl b/lib/mnesia/src/mnesia.erl
index a68b976993..69226443b4 100644
--- a/lib/mnesia/src/mnesia.erl
+++ b/lib/mnesia/src/mnesia.erl
@@ -655,7 +655,6 @@ ms() ->
      mnesia_late_loader,
      mnesia_lib,
      mnesia_log,
-     mnesia_registry,
      mnesia_schema,
      mnesia_snmp_hook,
      mnesia_subscr,
diff --git a/lib/mnesia/src/mnesia_registry.erl b/lib/mnesia/src/mnesia_registry.erl
index 5e2a313357..f1032bd0a4 100644
--- a/lib/mnesia/src/mnesia_registry.erl
+++ b/lib/mnesia/src/mnesia_registry.erl
@@ -22,312 +22,5 @@
 
 %%
 -module(mnesia_registry).
--moduledoc """
-This module is deprecated and the functions should not be used.
-
-This module was intended for internal use within OTP by the `erl_interface` application,
-but it has two functions that are exported for public use.
-
-Since the `erl_interface` have removed the registry functionality a long time ago,
-these functions are deprecated.
-
-## See Also
- `m:mnesia`
-""".
-
-%%%----------------------------------------------------------------------
-%%% File    : mnesia_registry.erl
-%%% Purpose : Support dump and restore of a registry on a C-node
-%%%           This is an OTP internal module and is not public available.
-%%%
-%%% Example : Dump some hardcoded records into the Mnesia table Tab
-%%%
-%%% 	  case rpc:call(Node, mnesia_registry, start_dump, [Tab, self()]) of
-%%% 	     Pid when pid(Pid) ->
-%%% 		 Pid ! {write, key1, key_size1, val_type1, val_size1, val1},
-%%% 		 Pid ! {delete, key3},
-%%% 		 Pid ! {write, key2, key_size2, val_type2, val_size2, val2},
-%%% 		 Pid ! {write, key4, key_size4, val_type4, val_size4, val4},
-%%% 		 Pid ! {commit, self()},
-%%% 		 receive
-%%% 		     {ok, Pid} ->
-%%% 			 ok;
-%%% 		     {'EXIT', Pid, Reason} ->
-%%% 			 exit(Reason)
-%%% 		 end;
-%%% 	     {badrpc, Reason} ->
-%%% 		 exit(Reason)
-%%% 	 end.
-%%%
-%%% Example : Restore the corresponding Mnesia table Tab
-%%%
-%%% 	  case rpc:call(Node, mnesia_registry, start_restore, [Tab, self()]) of
-%%% 	     {size, Pid, N, LargestKey, LargestVal} ->
-%%% 		 Pid ! {send_records, self()},
-%%%              Fun = fun() ->
-%%%                        receive
-%%%                            {restore, KeySize, ValSize, ValType, Key, Val} -> 
-%%%                                {Key, Val};
-%%% 		               {'EXIT', Pid, Reason} ->
-%%% 			           exit(Reason)
-%%%                        end
-%%% 		       end,
-%%%              lists:map(Fun, lists:seq(1, N));
-%%% 	     {badrpc, Reason} ->
-%%% 		 exit(Reason)
-%%% 	 end.
-%%%
-%%%----------------------------------------------------------------------
-
-%% External exports
-%% Avoid warning for local function max/2 clashing with autoimported BIF.
--compile({no_auto_import,[max/2]}).
--export([start_dump/2, start_restore/2]).
--export([create_table/1, create_table/2]).
-
--deprecated([{create_table, '_', "use mnesia:create_table/2 instead"}]).
-
-%% Internal exports
--export([init/4]).
-
--record(state, {table, ops = [], link_to}).
-
--record(registry_entry, {key, key_size, val_type, val_size, val}).
-
--record(size, {pid = self(), n_values = 0, largest_key = 0, largest_val = 0}).
-
-%%%----------------------------------------------------------------------
-%%% Client
-%%%----------------------------------------------------------------------
-
-start(Type, Tab, LinkTo) ->
-    Starter = self(),
-    Args = [Type, Starter, LinkTo, Tab],
-    Pid = spawn_link(?MODULE, init, Args),
-    %% The receiver process may unlink the current process
-    receive
-	{ok, Res} ->
-	    Res;
-	{'EXIT', Pid, Reason} when LinkTo == Starter ->
-	    exit(Reason)
-    end.
-
-%% Starts a receiver process and optionally creates a Mnesia table
-%% with suitable default values. Returns the Pid of the receiver process
-%% 
-%% The receiver process accumulates Mnesia operations and performs
-%% all operations or none at commit. The understood messages are:
-%% 
-%%    {write, Key, KeySize, ValType, ValSize, Val} ->
-%%        accumulates mnesia:write({Tab, Key, KeySize, ValType, ValSize, Val})
-%%                                                    (no reply)
-%%    {delete, Key}     ->
-%%        accumulates mnesia:delete({Tab, Key})       (no reply)
-%%    {commit, ReplyTo} ->
-%%        commits all accumulated operations
-%%        and stops the process                       (replies {ok, Pid})
-%%    abort             ->
-%%        stops the process                           (no reply)
-%%    
-%% The receiver process is linked to the process with the process identifier
-%% LinkTo. If some error occurs the receiver process will invoke exit(Reason)
-%% and it is up to he LinkTo process to act properly when it receives an exit
-%% signal.
-
--doc false.
-start_dump(Tab, LinkTo) ->
-    start(dump, Tab, LinkTo).
-
-%% Starts a sender process which sends restore messages back to the
-%% LinkTo process. But first are some statistics about the table
-%% determined and returned as a 5-tuple:
-%% 
-%%    {size, SenderPid, N, LargestKeySize, LargestValSize}
-%%
-%% where N is the number of records in the table. Then the sender process
-%% waits for a 2-tuple message:
-%% 
-%%    {send_records, ReplyTo}
-%%
-%% At last N 6-tuple messages is sent to the ReplyTo process:
-%% 
-%%    ReplyTo !  {restore, KeySize, ValSize, ValType, Key, Val}
-%%
-%% If some error occurs the receiver process will invoke exit(Reason)
-%% and it is up to he LinkTo process to act properly when it receives an
-%% exit signal.
-
--doc false.
-start_restore(Tab, LinkTo) ->
-    start(restore, Tab, LinkTo).
-
--doc """
-> #### Warning {: .warning }
->
-> _This function is deprecated. Do not use it._
->
-
-A wrapper function for `mnesia:create_table/2`, which creates a table (if there
-is no existing table) with an appropriate set of `attributes`. The table only
-resides on the local node and its storage type is the same as the `schema` table
-on the local node, that is, `{ram_copies,[node()]}` or `{disc_copies,[node()]}`.
-
-This function is used by `erl_interface` to create the Mnesia table if it does
-not already exist.
-""".
--spec create_table(Tab :: atom()) -> 'ok'.
-%% Optionally creates the Mnesia table Tab with suitable default values.
-%% Returns ok or EXIT's
-create_table(Tab) ->
-    Storage = mnesia:table_info(schema, storage_type),
-    create_table(Tab, [{Storage, [node()]}]).
-
--doc """
-> #### Warning {: .warning }
->
-> _This function is deprecated. Do not use it._
->
-
-A wrapper function for `mnesia:create_table/2`, which creates a table (if there
-is no existing table) with an appropriate set of `attributes`. The attributes
-and `TabDef` are forwarded to `mnesia:create_table/2`. For example, if the table
-is to reside as `disc_only_copies` on all nodes, a call looks as follows:
-
-```erlang
-          TabDef = [{{disc_only_copies, node()|nodes()]}],
-          mnesia_registry:create_table(my_reg, TabDef)
-```
-""".
--spec create_table(Tab :: atom(), Opt :: [{atom(), term()}]) -> ok.
-create_table(Tab, TabDef) ->
-    Attrs = record_info(fields, registry_entry),
-    case mnesia:create_table(Tab, [{attributes, Attrs} | TabDef]) of
-	{atomic, ok} ->
-	    ok;
-	{aborted, {already_exists, Tab}} ->
-	    ok;
-	{aborted, Reason} ->
-	    exit(Reason)
-    end.
-    
-%%%----------------------------------------------------------------------
-%%% Server
-%%%----------------------------------------------------------------------
-
--doc false.
-init(Type, Starter, LinkTo, Tab) ->
-    if
-	LinkTo /= Starter ->
-	    link(LinkTo),
-	    unlink(Starter);
-	true ->
-	    ignore
-    end,
-    case Type of
-	dump ->
-	    Starter ! {ok, self()},
-	    dump_loop(#state{table = Tab, link_to = LinkTo});
-	restore ->
-	    restore_table(Tab, Starter, LinkTo)
-    end.
-
-%%%----------------------------------------------------------------------
-%%% Dump loop    
-%%%----------------------------------------------------------------------
-
-dump_loop(S) ->
-    Tab = S#state.table,
-    Ops = S#state.ops,
-    receive
-	{write, Key, KeySize, ValType, ValSize, Val} ->
-	    RE = #registry_entry{key = Key,
-				 key_size = KeySize,
-				 val_type = ValType,
-				 val_size = ValSize,
-				 val = Val},
-	    dump_loop(S#state{ops = [{write, RE} | Ops]});
-	{delete, Key} ->
-	    dump_loop(S#state{ops = [{delete, Key} | Ops]});
-	{commit, ReplyTo} ->
-	    create_table(Tab),
-	    RecName = mnesia:table_info(Tab, record_name),
-	    %% The Ops are in reverse order, but there is no need
-	    %% for reversing the list of accumulated operations
-	    case mnesia:transaction(fun handle_ops/3, [Tab, RecName, Ops]) of
-                {atomic, ok} ->
-                    ReplyTo ! {ok, self()},
-                    stop(S#state.link_to);
-                {aborted, Reason} ->
-                    exit({aborted, Reason})
-            end;
-	abort ->
-	    stop(S#state.link_to);
-        BadMsg ->
-            exit({bad_message, BadMsg})					   
-    end.
-
-stop(LinkTo) ->
-    unlink(LinkTo),
-    exit(normal).
-
-%% Grab a write lock for the entire table
-%% and iterate over all accumulated operations
-handle_ops(Tab, RecName, Ops) ->
-    mnesia:write_lock_table(Tab),
-    do_handle_ops(Tab, RecName, Ops).
-
-do_handle_ops(Tab, RecName, [{write, RegEntry} | Ops]) ->
-    Record = setelement(1, RegEntry, RecName),
-    mnesia:write(Tab, Record, write),
-    do_handle_ops(Tab, RecName, Ops);
-do_handle_ops(Tab, RecName, [{delete, Key} | Ops]) ->
-    mnesia:delete(Tab, Key, write),
-    do_handle_ops(Tab, RecName, Ops);
-do_handle_ops(_Tab, _RecName, []) ->
-    ok.
-    
-%%%----------------------------------------------------------------------
-%%% Restore table
-%%%----------------------------------------------------------------------
-
-restore_table(Tab, Starter, LinkTo) ->
-    Pat = mnesia:table_info(Tab, wild_pattern),
-    Fun = fun() -> mnesia:match_object(Tab, Pat, read) end,
-    case mnesia:transaction(Fun) of
-	{atomic, AllRecords} ->
-	    Size = calc_size(AllRecords, #size{}),
-	    Starter ! {ok, Size},
-	    receive
-		{send_records, ReplyTo} -> 
-		    send_records(AllRecords, ReplyTo),
-		    unlink(LinkTo),
-		    exit(normal);
-		BadMsg ->
-		    exit({bad_message, BadMsg})
-	    end;
-	{aborted, Reason} ->
-            exit(Reason)
-    end.
-
-calc_size([H | T], S) ->
-    KeySize = max(element(#registry_entry.key_size, H), S#size.largest_key),
-    ValSize = max(element(#registry_entry.val_size, H), S#size.largest_val),
-    N = S#size.n_values + 1,
-    calc_size(T, S#size{n_values = N, largest_key = KeySize, largest_val = ValSize});
-calc_size([], Size) ->
-    Size.
-
-max(New, Old) when New > Old -> New;
-max(_New, Old) -> Old.
-
-send_records([H | T], ReplyTo) ->
-    KeySize = element(#registry_entry.key_size, H),
-    ValSize = element(#registry_entry.val_size, H),
-    ValType = element(#registry_entry.val_type, H),
-    Key = element(#registry_entry.key, H),
-    Val = element(#registry_entry.val, H),
-    ReplyTo ! {restore, KeySize, ValSize, ValType, Key, Val},
-    send_records(T, ReplyTo);
-send_records([], _ReplyTo) ->
-    ok.
 
+-removed([{create_table, '_', "use mnesia:create_table/2 instead"}]).
diff --git a/lib/mnesia/test/Makefile b/lib/mnesia/test/Makefile
index faae5c872f..45961ff1ab 100644
--- a/lib/mnesia/test/Makefile
+++ b/lib/mnesia/test/Makefile
@@ -32,7 +32,6 @@ MODULES= \
 	mnesia_bench_SUITE \
 	mnesia_test_lib \
 	mnesia_install_test \
-	mnesia_registry_test \
 	mnesia_config_test \
 	mnesia_frag_test \
 	mnesia_inconsistent_database_test \
diff --git a/lib/mnesia/test/mnesia_SUITE.erl b/lib/mnesia/test/mnesia_SUITE.erl
index cf56468119..fe18655f28 100644
--- a/lib/mnesia/test/mnesia_SUITE.erl
+++ b/lib/mnesia/test/mnesia_SUITE.erl
@@ -72,13 +72,12 @@ groups() ->
     [{light, [],
       [{group, install}, {group, nice}, {group, evil},
        {group, frag}, {group, qlc}, {group, index_plugins},
-       {group, registry}, {group, config}, {group, examples}]},
+       {group, config}, {group, examples}]},
      {install, [], [{mnesia_install_test, all}]},
      {nice, [], [{mnesia_nice_coverage_test, all}]},
      {evil, [], [{mnesia_evil_coverage_test, all}]},
      {qlc, [], [{mnesia_qlc_test, all}]},
      {index_plugins, [], [{mnesia_index_plugin_test, all}]},
-     {registry, [], [{mnesia_registry_test, all}]},
      {config, [], [{mnesia_config_test, all}]},
      {examples, [], [{mnesia_examples_test, all}]},
      {frag, [], [{mnesia_frag_test, all}]},
@@ -114,7 +113,7 @@ groups() ->
        {mnesia_evil_coverage_test, offline_set_master_nodes},
        {mnesia_evil_coverage_test, record_name},
        {mnesia_evil_coverage_test, user_properties},
-       {mnesia_registry_test, all}, {group, otp_2363}]},
+       {group, otp_2363}]},
      %% Index on disc only tables
      {otp_2363, [],
       [{mnesia_dirty_access_test,
diff --git a/lib/mnesia/test/mnesia_evil_coverage_test.erl b/lib/mnesia/test/mnesia_evil_coverage_test.erl
index 31df7a5864..e62676612d 100644
--- a/lib/mnesia/test/mnesia_evil_coverage_test.erl
+++ b/lib/mnesia/test/mnesia_evil_coverage_test.erl
@@ -2555,18 +2555,6 @@ record_name_dirty_access(Storage, Config) ->
     ?match([{some_counter, C, 4711}], mnesia:dirty_read(CounterTab, C)),
     ?match(0, mnesia:dirty_update_counter(CounterTab, C, -4747)),
 
-    %% Registry tests
-
-    RegTab = list_to_atom(lists:concat([Tab, "_registry"])),
-    RegTabDef = [{record_name, some_reg}],
-    ?match(ok, mnesia_registry:create_table(RegTab, RegTabDef)),
-    ?match(some_reg, mnesia:table_info(RegTab, record_name)),
-    {success, RegRecs} =
-	?match([_ | _], mnesia_registry_test:dump_registry(node(), RegTab)),
-
-    R = ?sort(RegRecs),
-    ?match(R, ?sort(mnesia_registry_test:restore_registry(node(), RegTab))),
-
     ?verify_mnesia(Nodes, []).
 
 sorted_ets(suite) ->
diff --git a/lib/mnesia/test/mnesia_registry_test.erl b/lib/mnesia/test/mnesia_registry_test.erl
deleted file mode 100644
index 0982a46a64..0000000000
--- a/lib/mnesia/test/mnesia_registry_test.erl
+++ /dev/null
@@ -1,148 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1998-2018. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-
-%%
--module(mnesia_registry_test).
--author('hakan@erix.ericsson.se').
--export([init_per_testcase/2, end_per_testcase/2,
-         init_per_group/2, end_per_group/2,
-         all/0, groups/0]).
-
--export([good_dump/1, bad_dump/1, dump_registry/2, restore_registry/2]).
-
--include("mnesia_test_lib.hrl").
-
-init_per_testcase(Func, Conf) ->
-    mnesia_test_lib:init_per_testcase(Func, Conf).
-
-end_per_testcase(Func, Conf) ->
-    mnesia_test_lib:end_per_testcase(Func, Conf).
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-all() -> 
-    [good_dump, bad_dump].
-
-groups() -> 
-    [].
-
-init_per_group(_GroupName, Config) ->
-    Config.
-
-end_per_group(_GroupName, Config) ->
-    Config.
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-good_dump(doc) ->
-    ["Dump a faked C-node registry"];
-good_dump(suite) -> [];
-good_dump(Config) when is_list(Config) ->
-    [Node] = Nodes = ?acquire_nodes(1, Config),
-    T1 = gordon,
-    ?match(ok, mnesia_registry:create_table(T1)),
-    One = {T1, 1, 0, integer, 0, 10},
-    Two = {T1, "two", 3, integer, 0, 20},
-    Three = {T1, 3, 0, string, 6, "thirty"},
-    ?match(ok, mnesia:dirty_write(One)),
-    ?match(ok, mnesia:dirty_write(Two)),
-    ?match(ok, mnesia:dirty_write(Three)),
-    ?match([One], mnesia:dirty_read({T1, 1})),
-    ?match([_ | _], dump_registry(Node, T1)),
-
-    NewOne = {T1, 1, 0, integer, 0, 1},
-    NewFour = {T1, "4", 1, string, 4, "four"},
-
-    ?match([NewOne], mnesia:dirty_read({T1, 1})),
-    ?match([Two], mnesia:dirty_read({T1, "two"})),
-    ?match([], mnesia:dirty_read({T1, 3})),
-    ?match([NewFour], mnesia:dirty_read({T1, "4"})),
-
-    T2 = blixt,
-    ?match({'EXIT', {aborted, {no_exists, _}}},
-	   mnesia:dirty_read({T2, 1})),
-    ?match([_ |_], dump_registry(Node, T2)),
-
-    NewOne2 = setelement(1, NewOne, T2),
-    NewFour2 = setelement(1, NewFour, T2),
-
-    ?match([NewOne2], mnesia:dirty_read({T2, 1})),
-    ?match([], mnesia:dirty_read({T2, "two"})),
-    ?match([], mnesia:dirty_read({T2, 3})),
-    ?match([NewFour2], mnesia:dirty_read({T2, "4"})),
-    ?match([_One2, NewFour2], lists:sort(restore_registry(Node, T2))),
-    
-    ?verify_mnesia(Nodes, []).
-
-dump_registry(Node, Tab) ->
-    case rpc:call(Node, mnesia_registry, start_dump, [Tab, self()]) of
-	Pid when is_pid(Pid) ->
-	    Pid ! {write, 1, 0, integer, 0, 1},
-	    Pid ! {delete, 3},
-	    Pid ! {write, "4", 1, string, 4, "four"},
-	    Pid ! {commit, self()},
-	    receive
-		{ok, Pid} ->
-		    [{Tab, "4", 1, string, 4, "four"},
-		     {Tab, 1, 0, integer, 0, 1}];
-		{'EXIT', Pid, Reason} ->
-		    exit(Reason)
-	    end;
-	{badrpc, Reason} ->
-	    exit(Reason)
-    end.
-
-restore_registry(Node, Tab) ->
-    case rpc:call(Node, mnesia_registry, start_restore, [Tab, self()]) of
-	{size, Pid, N, _LargestKeySize, _LargestValSize} ->
-	    Pid ! {send_records, self()},
-	    receive_records(Tab, N);
-	{badrpc, Reason} ->
-	    exit(Reason)
-    end.
-
-receive_records(Tab, N) when N > 0 ->
-    receive
-	{restore, KeySize, ValSize, ValType, Key, Val} -> 
-	    [{Tab, Key, KeySize, ValType, ValSize, Val} | receive_records(Tab, N -1)];
-	{'EXIT', _Pid, Reason} ->
-	    exit(Reason)
-    end;
-receive_records(_Tab, 0) ->
-    [].
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-bad_dump(doc) ->
-    ["Intentionally fail with the dump of a faked C-node registry"];
-bad_dump(suite) -> [];
-bad_dump(Config) when is_list(Config) ->
-    [Node] = Nodes = ?acquire_nodes(1, Config),
-    
-    OldTab = ming,
-    ?match({'EXIT', {aborted, _}}, mnesia_registry:start_restore(no_tab, self())),
-    ?match({atomic, ok}, mnesia:create_table(OldTab, [{attributes, [a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q]}])),
-    ?match({'EXIT',{aborted,{bad_type,_}}}, dump_registry(Node, OldTab)),
-    ?match(stopped, mnesia:stop()),
-
-    ?match({'EXIT', {aborted, _}}, mnesia_registry:create_table(down_table)),
-    ?match({'EXIT', {aborted, _}}, mnesia_registry:start_restore(no_tab, self())),
-    ?match({'EXIT', {aborted, _}}, dump_registry(Node, down_dump)),
-
-    ?verify_mnesia([], Nodes).
-
-- 
2.51.0

openSUSE Build Service is sponsored by