File 0328-erts-Remove-buggy-optimization-in-fun-purging.patch of Package erlang
From 5c1eab15b474a7eb0b4d97a73c16d3b45f22f891 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Thu, 1 Jun 2023 18:27:52 +0200
Subject: [PATCH] erts: Remove buggy optimization in fun purging
Calling a fun defined by a module that had been purged after
loading a different version of the same module (and therefore did
not inherit the old fun entries) could cause the emulator to
crash.
We could retain the optimization by comparing the MD5 of the old
and current instances, but it didn't give much so it's better to
just get rid of it.
Fixes #7288
---
erts/emulator/beam/beam_bif_load.c | 23 +++------
erts/emulator/test/code_SUITE.erl | 15 +++++-
.../test/code_SUITE_data/call_purged_fun.erl | 32 ++++++++++++
.../call_purged_fun_altered.erl | 37 ++++++++++++++
.../call_purged_fun_tester.erl | 49 +++++++++++++------
5 files changed, 124 insertions(+), 32 deletions(-)
create mode 100644 erts/emulator/test/code_SUITE_data/call_purged_fun.erl
create mode 100644 erts/emulator/test/code_SUITE_data/call_purged_fun_altered.erl
diff --git a/erts/emulator/beam/beam_bif_load.c b/erts/emulator/beam/beam_bif_load.c
index 148a848cf5..a4fc8632c6 100644
--- a/erts/emulator/beam/beam_bif_load.c
+++ b/erts/emulator/beam/beam_bif_load.c
@@ -1948,21 +1948,14 @@ BIF_RETTYPE erts_internal_purge_module_2(BIF_ALIST_2)
purge_state.module = BIF_ARG_1;
erts_mtx_unlock(&purge_state.mtx);
- /* Because fun calls always land in the latest instance, there
- * is no need to set up purge markers if there's current code
- * for this module. */
- if (!modp->curr.code_hdr) {
- /* Set up "pending purge" markers for the funs in this
- * module. Processes trying to call these funs will be
- * suspended _before_ calling them, which will then either
- * crash or succeed when resumed after the purge finishes
- * or is aborted.
- *
- * This guarantees that we won't get any more direct
- * references into the code while checking for such
- * funs. */
- erts_fun_purge_prepare(&modp->old);
- }
+ /* Set up "pending purge" markers for the funs in this module.
+ * Processes trying to call these funs will be suspended
+ * _before_ calling them, which will then either crash or
+ * succeed when resumed after the purge finishes or is aborted.
+ *
+ * This guarantees that we won't get any more direct references
+ * into the code while checking for such funs. */
+ erts_fun_purge_prepare(&modp->old);
res = am_true;
}
diff --git a/erts/emulator/test/code_SUITE.erl b/erts/emulator/test/code_SUITE.erl
index a1e63cd36c..f74df5ca71 100644
--- a/erts/emulator/test/code_SUITE.erl
+++ b/erts/emulator/test/code_SUITE.erl
@@ -26,6 +26,7 @@
call_purged_fun_code_gone/1,
call_purged_fun_code_reload/1,
call_purged_fun_code_there/1,
+ call_purged_fun_code_altered/1,
multi_proc_purge/1, t_check_old_code/1,
many_purges/1,
external_fun/1,get_chunk/1,module_md5/1,
@@ -47,6 +48,7 @@ all() ->
bad_beam_file, literal_leak,
call_purged_fun_code_gone,
call_purged_fun_code_reload, call_purged_fun_code_there,
+ call_purged_fun_code_altered,
multi_proc_purge, t_check_old_code, external_fun, get_chunk,
module_md5, many_purges,
constant_pools, constant_refc_binaries, fake_literals,
@@ -250,6 +252,18 @@ call_purged_fun_code_there_test(Config) when is_list(Config) ->
call_purged_fun_test(Priv, Data, code_there),
ok.
+%% GH-7288: calling a fun defined by a module that had been purged after
+%% loading a different version of the same module (and therefore did not
+%% inherit the old fun entries) could cause the emulator to crash.
+call_purged_fun_code_altered(Config) when is_list(Config) ->
+ run_sys_proc_test(fun call_purged_fun_code_altered_test/1, Config).
+
+call_purged_fun_code_altered_test(Config) when is_list(Config) ->
+ Priv = proplists:get_value(priv_dir, Config),
+ Data = proplists:get_value(data_dir, Config),
+ call_purged_fun_test(Priv, Data, code_altered),
+ ok.
+
call_purged_fun_test(Priv, Data, Type) ->
SrcFile = filename:join(Data, "call_purged_fun_tester.erl"),
ObjFile = filename:join(Priv, "call_purged_fun_tester.beam"),
@@ -258,7 +272,6 @@ call_purged_fun_test(Priv, Data, Type) ->
call_purged_fun_tester:do(Priv, Data, Type, []).
-
multi_proc_purge(Config) when is_list(Config) ->
run_sys_proc_test(fun multi_proc_purge_test/1, Config).
diff --git a/erts/emulator/test/code_SUITE_data/call_purged_fun.erl b/erts/emulator/test/code_SUITE_data/call_purged_fun.erl
new file mode 100644
index 0000000000..e3a94092dc
--- /dev/null
+++ b/erts/emulator/test/code_SUITE_data/call_purged_fun.erl
@@ -0,0 +1,32 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2023-2023. 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(call_purged_fun).
+
+-export([make_fun/1, make_fun2/0]).
+
+make_fun(A) ->
+ fun(X) -> A + X end.
+
+make_fun2() ->
+ fun (F1,F2) ->
+ F1(),
+ F2()
+ end.
diff --git a/erts/emulator/test/code_SUITE_data/call_purged_fun_altered.erl b/erts/emulator/test/code_SUITE_data/call_purged_fun_altered.erl
new file mode 100644
index 0000000000..6e180afdfe
--- /dev/null
+++ b/erts/emulator/test/code_SUITE_data/call_purged_fun_altered.erl
@@ -0,0 +1,37 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2023-2023. 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(call_purged_fun).
+
+-export([make_fun/1, make_fun2/0, dummy/1]).
+
+make_fun(A) ->
+ fun(X) -> A + X end.
+
+make_fun2() ->
+ fun (F1,F2) ->
+ F1(),
+ F2()
+ end.
+
+%% Dummy function that ensures the module MD5 is different from the alpha
+%% version, keeping us from inheriting its fun entries.
+dummy(I) ->
+ I.
diff --git a/erts/emulator/test/code_SUITE_data/call_purged_fun_tester.erl b/erts/emulator/test/code_SUITE_data/call_purged_fun_tester.erl
index 5ed5214c94..32494807c4 100644
--- a/erts/emulator/test/code_SUITE_data/call_purged_fun_tester.erl
+++ b/erts/emulator/test/code_SUITE_data/call_purged_fun_tester.erl
@@ -7,18 +7,18 @@ do(P,D,T,O) ->
do_it(P,D,T,O).
do_it(Priv, Data, Type, Opts) ->
- File = filename:join(Data, "my_code_test2"),
- Code = filename:join(Priv, "my_code_test2"),
+ OrigFile = filename:join(Data, "call_purged_fun"),
+ Code = filename:join(Priv, "call_purged_fun"),
- catch erlang:purge_module(my_code_test2),
- catch erlang:delete_module(my_code_test2),
- catch erlang:purge_module(my_code_test2),
+ catch erlang:purge_module(call_purged_fun),
+ catch erlang:delete_module(call_purged_fun),
+ catch erlang:purge_module(call_purged_fun),
- {ok,my_code_test2} = c:c(File, [{outdir,Priv} | Opts]),
+ {ok,call_purged_fun} = c:c(OrigFile, [{outdir,Priv} | Opts]),
- T = ets:new(my_code_test2_fun_table, []),
- ets:insert(T, {my_fun,my_code_test2:make_fun(4711)}),
- ets:insert(T, {my_fun2,my_code_test2:make_fun2()}),
+ T = ets:new(call_purged_fun_fun_table, []),
+ ets:insert(T, {my_fun,call_purged_fun:make_fun(4711)}),
+ ets:insert(T, {my_fun2,call_purged_fun:make_fun2()}),
Papa = self(),
{P0,M0} = spawn_monitor(fun () ->
@@ -37,30 +37,43 @@ do_it(Priv, Data, Type, Opts) ->
true;
code_reload ->
true;
+ code_altered ->
+ true;
code_there ->
false
end,
%% fun_info/1,2 must behave as documented on purged funs.
FunInfoBefore = fun(F) ->
- {module, my_code_test2} = erlang:fun_info(F, module),
+ {module, call_purged_fun} = erlang:fun_info(F, module),
{name, []} = erlang:fun_info(F, name),
{arity, 1} = erlang:fun_info(F, arity)
end,
FunInfoAfter = fun(F) ->
- {module, my_code_test2} = erlang:fun_info(F, module),
+ {module, call_purged_fun} = erlang:fun_info(F, module),
{name, Name} = erlang:fun_info(F, name),
true = is_atom(Name),
{arity, 1} = erlang:fun_info(F, arity)
end,
- true = erlang:delete_module(my_code_test2),
+ true = erlang:delete_module(call_purged_fun),
+
+ case Type of
+ code_altered ->
+ AlteredFile = filename:join(Data, "call_purged_fun_altered.erl"),
+ {ok,call_purged_fun,AlteredBin} =
+ compile:file(AlteredFile, [no_error_module_mismatch,
+ binary | Opts]),
+ code:load_binary(call_purged_fun, AlteredFile, AlteredBin);
+ _ ->
+ ok
+ end,
ok = receive {P0, "going to sleep"} -> ok
after 1000 -> timeout
end,
- Purge = start_purge(my_code_test2, PurgeType),
+ Purge = start_purge(call_purged_fun, PurgeType),
{P1, M1} = spawn_monitor(fun () ->
[{my_fun,F}] = ets:lookup(T, my_fun),
@@ -129,13 +142,17 @@ do_it(Priv, Data, Type, Opts) ->
{undef, _} = wait_for_down(P1,M1),
{undef, _} = wait_for_down(P2,M2),
{undef, _} = wait_for_down(P3,M3);
+ code_altered ->
+ {{badfun, _}, _} = wait_for_down(P1,M1),
+ {{badfun, _}, _} = wait_for_down(P2,M2),
+ {{badfun, _}, _} = wait_for_down(P3,M3);
_ ->
completed = wait_for_down(P1,M1),
completed = wait_for_down(P2,M2),
completed = wait_for_down(P3,M3),
- catch erlang:purge_module(my_code_test2),
- catch erlang:delete_module(my_code_test2),
- catch erlang:purge_module(my_code_test2)
+ catch erlang:purge_module(call_purged_fun),
+ catch erlang:delete_module(call_purged_fun),
+ catch erlang:purge_module(call_purged_fun)
end,
ok.
--
2.35.3