@@ -892,27 +892,26 @@ restart(Mod, Tid, Ts, Fun, Args, Factor0, Retries0, Type, Why) ->
892892 return_abort (Fun , Args , Why ),
893893 Factor = 1 ,
894894 SleepTime = mnesia_lib :random_time (Factor , Tid # tid .counter ),
895- dbg_out (" Restarting transaction ~w : in ~w ms ~w~n " , [Tid , SleepTime , Why ]),
895+ log_restart (" Restarting transaction ~w : in ~w ms ~w~n " , [Tid , SleepTime , Why ]),
896896 timer :sleep (SleepTime ),
897897 execute_outer (Mod , Fun , Args , Factor , Retries , Type );
898898 {node_not_running , _N } -> % % Avoids hanging in receive_release_tid_ack
899899 return_abort (Fun , Args , Why ),
900900 Factor = 1 ,
901901 SleepTime = mnesia_lib :random_time (Factor , Tid # tid .counter ),
902- dbg_out (" Restarting transaction ~w : in ~w ms ~w~n " , [Tid , SleepTime , Why ]),
902+ log_restart (" Restarting transaction ~w : in ~w ms ~w~n " , [Tid , SleepTime , Why ]),
903903 timer :sleep (SleepTime ),
904904 execute_outer (Mod , Fun , Args , Factor , Retries , Type );
905905 _ ->
906906 SleepTime = mnesia_lib :random_time (Factor0 , Tid # tid .counter ),
907907 dbg_out (" Restarting transaction ~w : in ~w ms ~w~n " , [Tid , SleepTime , Why ]),
908-
908+
909909 if
910910 Factor0 /= 10 ->
911911 ignore ;
912912 true ->
913913 % % Our serial may be much larger than other nodes ditto
914914 AllNodes = val ({current , db_nodes }),
915- verbose (" Sync serial ~p~n " , [Tid ]),
916915 rpc :abcast (AllNodes , ? MODULE , {sync_trans_serial , Tid })
917916 end ,
918917 intercept_friends (Tid , Ts ),
@@ -931,6 +930,24 @@ restart(Mod, Tid, Ts, Fun, Args, Factor0, Retries0, Type, Why) ->
931930 end
932931 end .
933932
933+ log_restart (F ,A ) ->
934+ case get (transaction_client ) of
935+ undefined ->
936+ dbg_out (F ,A );
937+ _ ->
938+ case get (transaction_count ) of
939+ undefined ->
940+ put (transaction_count , 1 ),
941+ verbose (F ,A );
942+ N when (N rem 10 ) == 0 ->
943+ put (transaction_count , N + 1 ),
944+ verbose (F ,A );
945+ N ->
946+ put (transaction_count , N + 1 ),
947+ dbg_out (F ,A )
948+ end
949+ end .
950+
934951get_restarted (Tid ) ->
935952 case Res = rec () of
936953 {restarted , Tid } ->
@@ -2086,6 +2103,7 @@ new_cr_format(#commit{ext=Snmp}=Cr) ->
20862103 Cr # commit {ext = [{snmp ,Snmp }]}.
20872104
20882105rec_all ([Node | Tail ], Tid , Res , Pids ) ->
2106+ put ({? MODULE , ? FUNCTION_NAME }, {Node , Tail }),
20892107 receive
20902108 {? MODULE , Node , {vote_yes , Tid }} ->
20912109 rec_all (Tail , Tid , Res , Pids );
@@ -2104,8 +2122,12 @@ rec_all([Node | Tail], Tid, Res, Pids) ->
21042122 Abort = {do_abort , {bad_commit , Node }},
21052123 ? SAFE ({? MODULE , Node } ! {Tid , Abort }),
21062124 rec_all (Tail , Tid , Abort , Pids )
2125+ after 15000 ->
2126+ mnesia_lib :verbose (" ~p : trans ~p waiting ~p~n " , [self (), Tid , Node ]),
2127+ rec_all ([Node | Tail ], Tid , Res , Pids )
21072128 end ;
21082129rec_all ([], _Tid , Res , Pids ) ->
2130+ erase ({? MODULE , ? FUNCTION_NAME }),
21092131 {Res , Pids }.
21102132
21112133get_transactions () ->
0 commit comments