File 2643-Use-a-separate-mnesia-rpc-server.patch of Package erlang

From 76060dde4c7921455c47c9cb66fb40ef66289090 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Tue, 26 Nov 2019 15:27:39 +0100
Subject: [PATCH 1/3] Use a separate mnesia rpc server

Do not overload erlangs rpc server, use an own server instead.
---
 lib/mnesia/src/Makefile              |  1 +
 lib/mnesia/src/mnesia.app.src        | 48 ++++++++++----------
 lib/mnesia/src/mnesia.erl            |  8 +++-
 lib/mnesia/src/mnesia_kernel_sup.erl |  1 +
 lib/mnesia/src/mnesia_monitor.erl    |  6 +--
 lib/mnesia/src/mnesia_rpc.erl        | 86 ++++++++++++++++++++++++++++++++++++
 lib/mnesia/src/mnesia_tm.erl         |  6 +--
 7 files changed, 126 insertions(+), 30 deletions(-)
 create mode 100644 lib/mnesia/src/mnesia_rpc.erl

diff --git a/lib/mnesia/src/Makefile b/lib/mnesia/src/Makefile
index 7d316df263..90e8780754 100644
--- a/lib/mnesia/src/Makefile
+++ b/lib/mnesia/src/Makefile
@@ -65,6 +65,7 @@ MODULES= \
 	mnesia_monitor \
 	mnesia_recover \
 	mnesia_registry \
+	mnesia_rpc \
 	mnesia_schema\
 	mnesia_snmp_hook \
 	mnesia_subscr \
diff --git a/lib/mnesia/src/mnesia.app.src b/lib/mnesia/src/mnesia.app.src
index c755b4d4b9..77bd1a7816 100644
--- a/lib/mnesia/src/mnesia.app.src
+++ b/lib/mnesia/src/mnesia.app.src
@@ -2,36 +2,37 @@
  [{description, "MNESIA  CXC 138 12"},
   {vsn, "%VSN%"},
   {modules, [
-	     mnesia, 
+	     mnesia,
 	     mnesia_app,
 	     mnesia_backend_type,
-	     mnesia_backup, 
-	     mnesia_bup, 
-	     mnesia_checkpoint, 
+	     mnesia_backup,
+	     mnesia_bup,
+	     mnesia_checkpoint,
 	     mnesia_checkpoint_sup,
 	     mnesia_controller,
-	     mnesia_dumper, 
-	     mnesia_event, 
+	     mnesia_dumper,
+	     mnesia_event,
 	     mnesia_ext_sup,
-	     mnesia_frag, 
-	     mnesia_frag_hash, 
-	     mnesia_index, 
+	     mnesia_frag,
+	     mnesia_frag_hash,
+	     mnesia_index,
              mnesia_kernel_sup,
 	     mnesia_late_loader,
-	     mnesia_lib, 
-	     mnesia_loader, 
-	     mnesia_locker, 
-	     mnesia_log, 
-	     mnesia_monitor, 
+	     mnesia_lib,
+	     mnesia_loader,
+	     mnesia_locker,
+	     mnesia_log,
+	     mnesia_monitor,
 	     mnesia_recover,
 	     mnesia_registry,
-	     mnesia_schema, 
-	     mnesia_snmp_hook, 
-	     mnesia_subscr, 
-	     mnesia_sup, 
+             mnesia_rpc,
+	     mnesia_schema,
+	     mnesia_snmp_hook,
+	     mnesia_subscr,
+	     mnesia_sup,
 	     mnesia_sp,
 	     mnesia_text,
-	     mnesia_tm 
+	     mnesia_tm
             ]},
   {registered, [
 		mnesia_dumper_load_regulator,
@@ -39,12 +40,13 @@
 		mnesia_fallback,
 		mnesia_controller,
 		mnesia_kernel_sup,
-		mnesia_late_loader, 
-		mnesia_locker, 
+		mnesia_late_loader,
+		mnesia_locker,
 		mnesia_monitor,
 		mnesia_recover,
-		mnesia_substr, 
-		mnesia_sup, 
+                mnesia_rpc,
+		mnesia_substr,
+		mnesia_sup,
 		mnesia_tm
 	       ]},
   {applications, [kernel, stdlib]},
diff --git a/lib/mnesia/src/mnesia.erl b/lib/mnesia/src/mnesia.erl
index 02bc884e36..aacea9a778 100644
--- a/lib/mnesia/src/mnesia.erl
+++ b/lib/mnesia/src/mnesia.erl
@@ -2057,8 +2057,14 @@ dirty_rpc(Tab, M, F, Args) ->
 
 do_dirty_rpc(_Tab, nowhere, _, _, Args) ->
     mnesia:abort({no_exists, Args});
+do_dirty_rpc(_Tab, Local, M, F, Args) when Local =:= node() ->
+    try apply(M,F,Args)
+    catch
+        throw:Res -> Res;
+        _:_ -> mnesia:abort({badarg, Args})
+    end;
 do_dirty_rpc(Tab, Node, M, F, Args) ->
-    case rpc:call(Node, M, F, Args) of
+    case mnesia_rpc:call(Node, M, F, Args) of
 	{badrpc, Reason} ->
 	    timer:sleep(20), %% Do not be too eager, and can't use yield on SMP
 	    %% Sync with mnesia_monitor
diff --git a/lib/mnesia/src/mnesia_kernel_sup.erl b/lib/mnesia/src/mnesia_kernel_sup.erl
index a761d5eed0..7f226d92c4 100644
--- a/lib/mnesia/src/mnesia_kernel_sup.erl
+++ b/lib/mnesia/src/mnesia_kernel_sup.erl
@@ -42,6 +42,7 @@ init([]) ->
 	       worker_spec(mnesia_locker, timer:seconds(3), ProcLib),
 	       worker_spec(mnesia_recover, timer:minutes(3), [gen_server]),
 	       worker_spec(mnesia_tm, timer:seconds(30), ProcLib),
+	       worker_spec(mnesia_rpc, timer:seconds(3), [gen_server]),
 	       supervisor_spec(mnesia_checkpoint_sup),
 	       worker_spec(mnesia_controller, timer:seconds(3), [gen_server]),
 	       worker_spec(mnesia_late_loader, timer:seconds(3), ProcLib)
diff --git a/lib/mnesia/src/mnesia_monitor.erl b/lib/mnesia/src/mnesia_monitor.erl
index 4e50b46da8..d1c22f2d58 100644
--- a/lib/mnesia/src/mnesia_monitor.erl
+++ b/lib/mnesia/src/mnesia_monitor.erl
@@ -83,9 +83,9 @@
 		going_down = [], tm_started = false, early_connects = [],
 		connecting, mq = [], remote_node_status = []}).
 
--define(current_protocol_version,  {8,4}).
+-define(current_protocol_version,  {8,5}).
 
--define(previous_protocol_version, {8,3}).
+-define(previous_protocol_version, {8,4}).
 
 start() ->
     gen_server:start_link({local, ?MODULE}, ?MODULE,
@@ -196,7 +196,7 @@ protocol_version() ->
 %% A sorted list of acceptable protocols the
 %% preferred protocols are first in the list
 acceptable_protocol_versions() ->
-    [protocol_version(), ?previous_protocol_version].
+    [protocol_version(), ?previous_protocol_version, {8,3}].
 
 needs_protocol_conversion(Node) ->
     case {?catch_val({protocol, Node}), protocol_version()} of
diff --git a/lib/mnesia/src/mnesia_rpc.erl b/lib/mnesia/src/mnesia_rpc.erl
new file mode 100644
index 0000000000..bbeacce9db
--- /dev/null
+++ b/lib/mnesia/src/mnesia_rpc.erl
@@ -0,0 +1,86 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019. 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%
+%%
+
+%% Don't use the system rpc server since it may overload other
+%% applications when using a lot of dirty read operations.
+
+-module(mnesia_rpc).
+-behaviour(gen_server).
+
+-export([start/0,
+         call/4
+        ]).
+
+
+%% gen_server callbacks
+-export([init/1,
+	 handle_call/3,
+	 handle_cast/2,
+	 handle_info/2,
+	 terminate/2,
+	 code_change/3
+	]).
+
+-include("mnesia.hrl").
+
+start() ->
+    gen_server:start_link({local, ?MODULE}, ?MODULE, [self()],
+			  [{timeout, infinity} %%, {debug, [trace]}
+			  ]).
+
+call(Node, M, F, Args) ->
+    case ?catch_val({protocol, Node}) of
+        {Ver, _} when Ver < {8,5} ->
+            rpc:call(Node, M, F, Args);
+        _ ->
+            try gen_server:call({?MODULE, Node}, {apply, M, F, Args}, infinity)
+            catch
+                _:Reason -> {badrpc, {'EXIT', Reason}}
+            end
+    end.
+
+init([_Parent]) ->
+    {ok, #{}}.
+
+handle_call({apply, Mod, Fun, Args}, _From, State) ->
+    %% rpc is just for ets:lookups so no need to spawn requests
+    Result = try apply(Mod, Fun, Args)
+             catch throw:Res -> Res;
+                   _:Reason -> {badrpc, {'EXIT', Reason}}
+             end,
+    {reply, Result, State};
+handle_call(Msg, _From, State) ->
+    error("~p got unexpected call: ~tp~n", [?MODULE, Msg]),
+    {reply, badop, State}.
+
+handle_cast(Msg, State) ->
+    mnesia_lib:error("~p got unexpected cast: ~tp~n", [?MODULE, Msg]),
+    {noreply, State}.
+
+handle_info(Msg, State) ->
+    mnesia_lib:error("~p got unexpected info: ~tp~n", [?MODULE, Msg]),
+    {noreply, State}.
+
+
+code_change(_OldVsn, State, _Extra) ->
+    {ok, State}.
+
+terminate(_Reason, _State) ->
+    ok.
diff --git a/lib/mnesia/src/mnesia_tm.erl b/lib/mnesia/src/mnesia_tm.erl
index 18520423ba..41e7ddce87 100644
--- a/lib/mnesia/src/mnesia_tm.erl
+++ b/lib/mnesia/src/mnesia_tm.erl
@@ -2082,9 +2082,9 @@ ask_commit(_Protocol, _Tid, [], _DiscNs, _RamNs, WaitFor, Local) ->
     {WaitFor, Local}.
 
 convert_old(sync_asym_trans, Node) ->
-    case mnesia_monitor:needs_protocol_conversion(Node) of
-        true -> asym_trans;
-        false -> sync_asym_trans
+    case ?catch_val({protocol, Node}) of
+        {{8,3}, _} -> asym_trans;
+        _ -> sync_asym_trans
     end;
 convert_old(Protocol, _) ->
     Protocol.
-- 
2.16.4

openSUSE Build Service is sponsored by