File 0790-Fix-mnesia-crash-when-checkpoint-initialization-fail.patch of Package erlang

From de2261cda59222d2494424178a4122630ef2ecd6 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Wed, 20 Nov 2024 14:26:37 +0100
Subject: [PATCH] Fix mnesia crash when checkpoint initialization fails

If a table is deleted just when a checkpoint is starting,
the checkpoint creation could fail so that mnesia crashed.
---
 lib/mnesia/src/mnesia_checkpoint.erl          | 30 +++++++++++--------
 lib/mnesia/test/mnesia_evil_coverage_test.erl | 21 +++++++++++--
 2 files changed, 36 insertions(+), 15 deletions(-)

diff --git a/lib/mnesia/src/mnesia_checkpoint.erl b/lib/mnesia/src/mnesia_checkpoint.erl
index fce588444b..2c22f909b4 100644
--- a/lib/mnesia/src/mnesia_checkpoint.erl
+++ b/lib/mnesia/src/mnesia_checkpoint.erl
@@ -617,24 +617,28 @@ init(Cp) ->
     Name = Cp#checkpoint_args.name,
     Props = [set, public, {keypos, 2}],
     try ?ets_new_table(mnesia_pending_checkpoint, Props) of
-	PendingTab ->
-	    Rs = [prepare_tab(Cp, R) || R <- Cp#checkpoint_args.retainers],
-	    Cp2 = Cp#checkpoint_args{retainers = Rs,
-				pid = self(),
-				pending_tab = PendingTab},
-	    add(pending_checkpoint_pids, self()),
-	    add(pending_checkpoints, PendingTab),
-	    set({checkpoint, Name}, self()),
-	    add(checkpoints, Name),
-	    dbg_out("Checkpoint ~p (~p) started~n", [Name, self()]),
-	    proc_lib:init_ack(Cp2#checkpoint_args.supervisor, {ok, self()}),
-	    retainer_loop(Cp2)
+        PendingTab ->
+            try [prepare_tab(Cp, R) || R <- Cp#checkpoint_args.retainers] of
+                Rs ->
+                    Cp2 = Cp#checkpoint_args{retainers = Rs,
+                                             pid = self(),
+                                             pending_tab = PendingTab},
+                    add(pending_checkpoint_pids, self()),
+                    add(pending_checkpoints, PendingTab),
+                    set({checkpoint, Name}, self()),
+                    add(checkpoints, Name),
+                    dbg_out("Checkpoint ~p (~p) started~n", [Name, self()]),
+                    proc_lib:init_ack(Cp2#checkpoint_args.supervisor, {ok, self()}),
+                    retainer_loop(Cp2)
+            catch exit:Reason ->
+                    proc_lib:init_ack(Cp#checkpoint_args.supervisor, {error, Reason})
+            end
     catch error:Reason -> %% system limit
 	    Msg = "Cannot create an ets table for pending transactions",
 	    Error = {error, {system_limit, Name, Msg, Reason}},
 	    proc_lib:init_ack(Cp#checkpoint_args.supervisor, Error)
     end.
-    
+
 prepare_tab(Cp, R) ->
     Tab = R#retainer.tab_name,
     prepare_tab(Cp, R, val({Tab, storage_type})).
diff --git a/lib/mnesia/test/mnesia_evil_coverage_test.erl b/lib/mnesia/test/mnesia_evil_coverage_test.erl
index 3a697ba16d..3d99ebdf7a 100644
--- a/lib/mnesia/test/mnesia_evil_coverage_test.erl
+++ b/lib/mnesia/test/mnesia_evil_coverage_test.erl
@@ -29,7 +29,7 @@
 
 -export([system_info/1, table_info/1, error_description/1,
          db_node_lifecycle/1, evil_delete_db_node/1, start_and_stop/1,
-         checkpoint/1, table_lifecycle/1, storage_options/1,
+         checkpoint/1, checkpoint_del_table/1, table_lifecycle/1, storage_options/1,
          add_copy_conflict/1, add_copy_when_going_down/1, add_copy_when_dst_going_down/1,
          add_copy_with_down/1,
          replica_management/1, clear_table_during_load/1,
@@ -64,7 +64,8 @@ end_per_testcase(Func, Conf) ->
 all() -> 
     [system_info, table_info, error_description,
      db_node_lifecycle, evil_delete_db_node, start_and_stop,
-     checkpoint, table_lifecycle, storage_options, 
+     checkpoint, checkpoint_del_table,
+     table_lifecycle, storage_options,
      add_copy_conflict,
      add_copy_when_going_down, add_copy_when_dst_going_down, add_copy_with_down,
      replica_management,
@@ -460,6 +461,22 @@ checkpoint(NodeConfig, Config) ->
     lists:foreach(Fun, Tabs),
     ?verify_mnesia(TabNodes, []).
 
+
+checkpoint_del_table(Config) when is_list(Config) ->
+    [Node1] = ?acquire_nodes(1, Config),
+    [mnesia:create_table(list_to_atom("a_" ++ integer_to_list(I)), []) || I <- lists:seq(1, 1000)],
+
+    Tabs = mnesia:system_info(local_tables),
+
+    spawn(fun() ->
+                  mnesia:activate_checkpoint([{max, Tabs},{ram_overrides_dump, true}])
+          end),
+
+    {atomic, ok} = mnesia:delete_table(a_10),
+    %% Ensure we didn't crash
+
+    ?verify_mnesia([Node1], []).
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% Create and delete tables
 
-- 
2.43.0

openSUSE Build Service is sponsored by