File 2641-mnesia-Introduce-sync_asym_trans-protocol.patch of Package erlang

From edfeb5d9b7dcba2380f629b5a41cbab65cd40cb8 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Thu, 25 Jul 2019 11:07:28 +0200
Subject: [PATCH 1/2] mnesia: Introduce sync_asym_trans protocol

Transactions with sticky locks could with async_asym transactions be
committed in the wrong order, since asym transaction are spawned on
the remote nodes.

See ERL-768.
---
 lib/mnesia/src/mnesia_locker.erl |  2 ++
 lib/mnesia/src/mnesia_tm.erl     | 75 ++++++++++++++++++++++++----------------
 lib/mnesia/test/mt               | 38 +++++++++++++++-----
 3 files changed, 78 insertions(+), 37 deletions(-)

diff --git a/lib/mnesia/src/mnesia_locker.erl b/lib/mnesia/src/mnesia_locker.erl
index f68626413e..0222c5b1a0 100644
--- a/lib/mnesia/src/mnesia_locker.erl
+++ b/lib/mnesia/src/mnesia_locker.erl
@@ -774,10 +774,12 @@ do_sticky_lock(Tid, Store, {Tab, Key} = Oid, Lock) ->
     N = node(),
     receive
 	{?MODULE, N, granted} ->
+            ?ets_insert(Store, {sticky, true}),
 	    ?ets_insert(Store, {{locks, Tab, Key}, write}),
 	    [?ets_insert(Store, {nodes, Node}) || Node <- WNodes],
 	    granted;
 	{?MODULE, N, {granted, Val}} -> %% for rwlocks
+            ?ets_insert(Store, {sticky, true}),
 	    case opt_lookup_in_client(Val, Oid, write) of
 		C = #cyclic{} ->
 		    exit({aborted, C});
diff --git a/lib/mnesia/src/mnesia_tm.erl b/lib/mnesia/src/mnesia_tm.erl
index 8b79fca1d7..1fa920321b 100644
--- a/lib/mnesia/src/mnesia_tm.erl
+++ b/lib/mnesia/src/mnesia_tm.erl
@@ -26,7 +26,7 @@
 	 init/1,
 	 non_transaction/5,
 	 transaction/6,
-	 commit_participant/5,
+	 commit_participant/6,
 	 dirty/2,
 	 display_info/2,
 	 do_update_op/3,
@@ -62,13 +62,14 @@
 %% Format on coordinators is [{Tid, EtsTabList} .....
 
 -record(prep, {protocol = sym_trans,
-	       %% async_dirty | sync_dirty | sym_trans | sync_sym_trans | asym_trans
+	       %% async_dirty | sync_dirty | sym_trans | sync_sym_trans | asym_trans | sync_asym_trans
 	       records = [],
 	       prev_tab = [], % initiate to a non valid table name
 	       prev_types,
 	       prev_snmp,
 	       types,
-	       majority = []
+	       majority = [],
+               sync = false
 	      }).
 
 -record(participant, {tid, pid, commit, disc_nodes = [],
@@ -250,11 +251,13 @@ doit_loop(#state{coordinators=Coordinators,participants=Participants,supervisor=
 	    mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
 	    Commit = new_cr_format(Commit0),
 	    Pid =
-		case Protocol of
-		    asym_trans when node(Tid#tid.pid) /= node() ->
-			Args = [tmpid(From), Tid, Commit, DiscNs, RamNs],
+                if
+                    node(Tid#tid.pid) =:= node() ->
+                        error({internal_error, local_node});
+                    Protocol =:= asym_trans orelse Protocol =:= sync_asym_trans ->
+			Args = [Protocol, tmpid(From), Tid, Commit, DiscNs, RamNs],
 			spawn_link(?MODULE, commit_participant, Args);
-		    _ when node(Tid#tid.pid) /= node() -> %% *_sym_trans
+                    true -> %% *_sym_trans
 			reply(From, {vote_yes, Tid}),
 			nopid
 		end,
@@ -1190,7 +1193,15 @@ do_arrange(Tid, Store, RestoreKey, Prep, N) when RestoreKey == restore_op ->
     P2 = Prep#prep{protocol = asym_trans, records = Recs2},
     do_arrange(Tid, Store, ?ets_next(Store, RestoreKey), P2, N + 1);
 do_arrange(_Tid, _Store, '$end_of_table', Prep, N) ->
-    {N, Prep};
+    case Prep of
+        #prep{sync=true, protocol=asym_trans} ->
+            {N, Prep#prep{protocol=sync_asym_trans}};
+        _ ->
+            {N, Prep}
+    end;
+do_arrange(Tid, Store, sticky, Prep, N) ->
+    P2 = Prep#prep{sync=true},
+    do_arrange(Tid, Store, ?ets_next(Store, sticky), P2, N);
 do_arrange(Tid, Store, IgnoredKey, Prep, N) -> %% locks, nodes ... local atoms...
     do_arrange(Tid, Store, ?ets_next(Store, IgnoredKey), Prep, N).
 
@@ -1448,7 +1459,8 @@ multi_commit(sync_sym_trans, _Maj = [], Tid, CR, Store) ->
 		    [{tid, Tid}, {outcome, Outcome}]),
     Outcome;
 
-multi_commit(asym_trans, Majority, Tid, CR, Store) ->
+multi_commit(Protocol, Majority, Tid, CR, Store)
+  when Protocol =:= asym_trans; Protocol =:= sync_asym_trans ->
     %% This more expensive commit protocol is used when
     %% table definitions are changed (schema transactions).
     %% It is also used when the involved tables are
@@ -1515,7 +1527,7 @@ multi_commit(asym_trans, Majority, Tid, CR, Store) ->
     end,
     Pending = mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
     ?ets_insert(Store, Pending),
-    {WaitFor, Local} = ask_commit(asym_trans, Tid, CR2, DiscNs, RamNs),
+    {WaitFor, Local} = ask_commit(Protocol, Tid, CR2, DiscNs, RamNs),
     SchemaPrep = ?CATCH(mnesia_schema:prepare_commit(Tid, Local, {coord, WaitFor})),
     {Votes, Pids} = rec_all(WaitFor, Tid, do_commit, []),
 
@@ -1563,38 +1575,38 @@ multi_commit(asym_trans, Majority, Tid, CR, Store) ->
 
 %% Returns do_commit or {do_abort, Reason}
 rec_acc_pre_commit([Pid | Tail], Tid, Store, Commit, Res, DumperMode,
-		   GoodPids, SchemaAckPids) ->
+		   GoodPids, AckPids) ->
     receive
 	{?MODULE, _, {acc_pre_commit, Tid, Pid, true}} ->
 	    rec_acc_pre_commit(Tail, Tid, Store, Commit, Res, DumperMode,
-			       [Pid | GoodPids], [Pid | SchemaAckPids]);
+			       [Pid | GoodPids], [Pid | AckPids]);
 
 	{?MODULE, _, {acc_pre_commit, Tid, Pid, false}} ->
 	    rec_acc_pre_commit(Tail, Tid, Store, Commit, Res, DumperMode,
-			       [Pid | GoodPids], SchemaAckPids);
+			       [Pid | GoodPids], AckPids);
 
 	{?MODULE, _, {acc_pre_commit, Tid, Pid}} ->
 	    %% Kept for backwards compatibility. Remove after Mnesia 4.x
 	    rec_acc_pre_commit(Tail, Tid, Store, Commit, Res, DumperMode,
-			       [Pid | GoodPids], [Pid | SchemaAckPids]);
+			       [Pid | GoodPids], [Pid | AckPids]);
 	{?MODULE, _, {do_abort, Tid, Pid, _Reason}} ->
 	    AbortRes = {do_abort, {bad_commit, node(Pid)}},
 	    rec_acc_pre_commit(Tail, Tid, Store, Commit, AbortRes, DumperMode,
-			       GoodPids, SchemaAckPids);
+			       GoodPids, AckPids);
 	{mnesia_down, Node} when Node == node(Pid) ->
 	    AbortRes = {do_abort, {bad_commit, Node}},
 	    ?SAFE(Pid ! {Tid, AbortRes}),  %% Tell him that he has died
 	    rec_acc_pre_commit(Tail, Tid, Store, Commit, AbortRes, DumperMode,
-			       GoodPids, SchemaAckPids)
+			       GoodPids, AckPids)
     end;
-rec_acc_pre_commit([], Tid, Store, {Commit,OrigC}, Res, DumperMode, GoodPids, SchemaAckPids) ->
+rec_acc_pre_commit([], Tid, Store, {Commit,OrigC}, Res, DumperMode, GoodPids, AckPids) ->
     D = Commit#commit.decision,
     case Res of
 	do_commit ->
 	    %% Now everybody knows that the others
 	    %% has voted yes. We also know that
 	    %% everybody are uncertain.
-	    prepare_sync_schema_commit(Store, SchemaAckPids),
+	    prepare_sync_schema_commit(Store, AckPids),
 	    tell_participants(GoodPids, {Tid, committed}),
 	    D2 = D#decision{outcome = committed},
 	    mnesia_recover:log_decision(D2),
@@ -1606,7 +1618,7 @@ rec_acc_pre_commit([], Tid, Store, {Commit,OrigC}, Res, DumperMode, GoodPids, Sc
 	    do_commit(Tid, Commit, DumperMode),
             ?eval_debug_fun({?MODULE, rec_acc_pre_commit_done_commit},
 			    [{tid, Tid}]),
-	    sync_schema_commit(Tid, Store, SchemaAckPids),
+	    sync_schema_commit(Tid, Store, AckPids),
 	    mnesia_locker:release_tid(Tid),
 	    ?MODULE ! {delete_transaction, Tid};
 
@@ -1623,6 +1635,7 @@ rec_acc_pre_commit([], Tid, Store, {Commit,OrigC}, Res, DumperMode, GoodPids, Sc
     Res.
 
 %% Note all nodes in case of mnesia_down mgt
+%% sync_schema_commit is (ab)used for sync_asym_trans as well.
 prepare_sync_schema_commit(_Store, []) ->
     ok;
 prepare_sync_schema_commit(Store, [Pid | Pids]) ->
@@ -1648,17 +1661,17 @@ tell_participants([Pid | Pids], Msg) ->
 tell_participants([], _Msg) ->
     ok.
 
--spec commit_participant(_, _, _, _, _) -> no_return().
+-spec commit_participant(_, _, _, _, _, _) -> no_return().
 %% Trap exit because we can get a shutdown from application manager
-commit_participant(Coord, Tid, Bin, DiscNs, RamNs) when is_binary(Bin) ->
+commit_participant(Protocol, Coord, Tid, Bin, DiscNs, RamNs) when is_binary(Bin) ->
     process_flag(trap_exit, true),
     Commit = binary_to_term(Bin),
-    commit_participant(Coord, Tid, Bin, Commit, DiscNs, RamNs);
-commit_participant(Coord, Tid, C = #commit{}, DiscNs, RamNs) ->
+    commit_participant(Protocol, Coord, Tid, Bin, Commit, DiscNs, RamNs);
+commit_participant(Protocol, Coord, Tid, C = #commit{}, DiscNs, RamNs) ->
     process_flag(trap_exit, true),
-    commit_participant(Coord, Tid, C, C, DiscNs, RamNs).
+    commit_participant(Protocol, Coord, Tid, C, C, DiscNs, RamNs).
 
-commit_participant(Coord, Tid, Bin, C0, DiscNs, _RamNs) ->
+commit_participant(Protocol, Coord, Tid, Bin, C0, DiscNs, _RamNs) ->
     ?eval_debug_fun({?MODULE, commit_participant, pre}, [{tid, Tid}]),
     try mnesia_schema:prepare_commit(Tid, C0, {part, Coord}) of
 	{Modified, C = #commit{}, DumperMode} ->
@@ -1683,8 +1696,9 @@ commit_participant(Coord, Tid, Bin, C0, DiscNs, _RamNs) ->
 		    mnesia_recover:log_decision(D#decision{outcome = unclear}),
 		    ?eval_debug_fun({?MODULE, commit_participant, pre_commit},
 				    [{tid, Tid}]),
-		    Expect_schema_ack = C#commit.schema_ops /= [],
-		    reply(Coord, {acc_pre_commit, Tid, self(), Expect_schema_ack}),
+		    ExpectAck = C#commit.schema_ops /= []
+                        orelse Protocol =:= sync_asym_trans,
+		    reply(Coord, {acc_pre_commit, Tid, self(), ExpectAck}),
 
 		    %% Now we are vulnerable for failures, since
 		    %% we cannot decide without asking others
@@ -1694,7 +1708,7 @@ commit_participant(Coord, Tid, Bin, C0, DiscNs, _RamNs) ->
 			    ?eval_debug_fun({?MODULE, commit_participant, log_commit},
 					    [{tid, Tid}]),
 			    do_commit(Tid, C, DumperMode),
-			    case Expect_schema_ack of
+			    case ExpectAck of
 				false -> ignore;
 				true -> reply(Coord, {schema_commit, Tid, self()})
 			    end,
@@ -2304,7 +2318,7 @@ reconfigure_participants(_, []) ->
 %% tell mnesia_tm on all involved nodes (including the local node)
 %% about the outcome.
 tell_outcome(Tid, Protocol, Node, CheckNodes, TellNodes) ->
-    Outcome = mnesia_recover:what_happened(Tid, Protocol, CheckNodes),
+    Outcome = mnesia_recover:what_happened(Tid, proto(Protocol), CheckNodes),
     case Outcome of
 	aborted ->
 	    rpc:abcast(TellNodes, ?MODULE, {Tid,{do_abort, {mnesia_down, Node}}});
@@ -2313,6 +2327,9 @@ tell_outcome(Tid, Protocol, Node, CheckNodes, TellNodes) ->
     end,
     Outcome.
 
+proto(sync_asym_trans) -> asym_trans;
+proto(Proto) -> Proto.
+
 do_stop(#state{coordinators = Coordinators}) ->
     Msg = {mnesia_down, node()},
     lists:foreach(fun({Tid, _}) -> Tid#tid.pid ! Msg end, gb_trees:to_list(Coordinators)),
diff --git a/lib/mnesia/test/mt b/lib/mnesia/test/mt
index a398ee0422..b169734f56 100755
--- a/lib/mnesia/test/mt
+++ b/lib/mnesia/test/mt
@@ -34,8 +34,35 @@ erlcmd="erl -sname a $p $args -mnesia_test_timeout"
 erlcmd1="erl -sname a1 $p $args"
 erlcmd2="erl -sname a2 $p $args"
 
-xterm -geometry 70x20+0+550 -T a1 -e $erlcmd1 &
-xterm -geometry 70x20+450+550 -T a2 -e $erlcmd2 &
+if test z"$MT_TERM" = z ; then
+    MT_TERM=xterm
+fi
+
+case $MT_TERM in
+    xterm)
+	geom0="-geometry 142x40+0+0"
+	geom1="-geometry 70x20+0+550"
+	geom2="-geometry 70x20+480+550"
+	title="-T"
+	exec="-e"
+	;;
+    gnome-terminal)
+	geom0="--geometry 142x40+0+0"
+	geom1="--geometry 70x20+0+740"
+	geom2="--geometry 70x20+700+740"
+	title="--title"
+	exec="--hide-menubar --"
+	;;
+    *rxvt)
+	geom0="-geometry 142x40+0+0"
+	geom1="-geometry 70x20+0+680"
+	geom2="-geometry 70x20+630+680"
+	title="-title"
+	exec="-e"
+esac
+
+$MT_TERM $geom1 $title a1 $exec $erlcmd1 &
+$MT_TERM $geom2 $title a2 $exec $erlcmd2 &
 
 rm "$latest" 2>/dev/null
 ln -s "$log" "$latest"
@@ -51,11 +78,6 @@ echo "Give the following command in order to see the outcome from node a@$h"":"
 echo ""
 echo "	less test_log$$"
 
-ostype=`uname -s`
-if [ "$ostype" = "SunOS" ] ; then 
-  /usr/openwin/bin/xterm -geometry 145x40+0+0 -T a -l -lf "$log" -e $erlcmd &
-else
-  xterm -geometry 145x40+0+0 -T a -e script -f -c "$erlcmd" "$log"  &
-fi
+$MT_TERM $geom0 $title a $exec script -f -c "$erlcmd" "$log"  &
 tail -f "$log" | egrep 'Eval|<>ERROR|NYI'
 
-- 
2.16.4

openSUSE Build Service is sponsored by