File 1348-erts-Fix-write-after-free-bug-for-DistEntry-AGAIN.patch of Package erlang
From fcd81a3c4ce7b1ceceb73d030723d2d4a0985873 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Tue, 15 Jun 2021 12:56:15 +0200
Subject: [PATCH] erts: Fix write-after-free bug for DistEntry (AGAIN)
Symptom:
VM crash caused by write-after-free on reference counter of DistEntry
magic binary (GH-4964).
Problem:
DistEntry reference counter too low and is therefore decremented after
deallocation.
This problem was earlier tried to be fixed by 348b9ba8045c3d71d87f826d15fca145999a1593
with a call to erts_refc_inc_if() in erts_build_dhandle(), but that
was not race-free as this scenario shows:
Scenario:
0. DistEntry refc = 1
1. Thread A do lookup of DistEntry without refc++
2. Thread A calls erts_build_dhandle()
erts_refc_inc_if(0) does nothing as refc=1
3. Thread B do refc-- from 1 to 0 and schedules pending delete.
4. Thread A calls erts_mk_magic_ref() that does refc++ from 0 to 1
5. Thread B executes pending delete and does refc-- from 1 to 0.
DistEntry now has refc==0 while it's referred by a live dhandle term
which may later lead to write-after-free on the reference counter.
Solution:
Replace erts_refc_inc_if(0) in erts_build_dhandle()
with a combination of erts_refc_inctest()
followed by a conditional erts_refc_inc().
This is similar to the other places where we do an extra refc bump
for pending delete.
---
erts/emulator/beam/erl_bif_unique.h | 14 ++++++-
erts/emulator/beam/erl_node_tables.c | 7 +++-
erts/emulator/test/distribution_SUITE.erl | 45 +++++++++++++++++++++++
3 files changed, 62 insertions(+), 4 deletions(-)
diff --git a/erts/emulator/beam/erl_bif_unique.h b/erts/emulator/beam/erl_bif_unique.h
index 41fce533d6..bda9a50d25 100644
--- a/erts/emulator/beam/erl_bif_unique.h
+++ b/erts/emulator/beam/erl_bif_unique.h
@@ -87,6 +87,7 @@ ERTS_GLB_INLINE void erts_sched_make_magic_ref_in_array(ErtsSchedulerData *esdp,
Uint32 ref[ERTS_REF_NUMBERS]);
ERTS_GLB_INLINE Eterm erts_sched_make_ref_in_buffer(ErtsSchedulerData *esdp,
Eterm buffer[ERTS_REF_THING_SIZE]);
+ERTS_GLB_INLINE Eterm erts_mk_magic_ref_get_refc(Eterm * *hpp, ErlOffHeap * ohp, Binary*, erts_aint_t*);
ERTS_GLB_INLINE Eterm erts_mk_magic_ref(Eterm **hpp, ErlOffHeap *ohp, Binary *mbp);
ERTS_GLB_INLINE Binary *erts_magic_ref2bin(Eterm mref);
ERTS_GLB_INLINE void erts_magic_ref_save_bin(Eterm ref);
@@ -175,17 +176,26 @@ erts_sched_make_ref_in_buffer(ErtsSchedulerData *esdp,
}
ERTS_GLB_INLINE Eterm
-erts_mk_magic_ref(Eterm **hpp, ErlOffHeap *ohp, Binary *bp)
+erts_mk_magic_ref_get_refc(Eterm **hpp, ErlOffHeap *ohp, Binary *bp, erts_aint_t* refcp)
{
Eterm *hp = *hpp;
ASSERT(bp->intern.flags & BIN_FLAG_MAGIC);
write_magic_ref_thing(hp, ohp, (ErtsMagicBinary *) bp);
*hpp += ERTS_MAGIC_REF_THING_SIZE;
- erts_refc_inc(&bp->intern.refc, 1);
+ if (refcp)
+ *refcp = erts_refc_inctest(&bp->intern.refc, 1);
+ else
+ erts_refc_inc(&bp->intern.refc, 1);
OH_OVERHEAD(ohp, bp->orig_size / sizeof(Eterm));
return make_internal_ref(hp);
}
+ERTS_GLB_INLINE Eterm
+erts_mk_magic_ref(Eterm **hpp, ErlOffHeap *ohp, Binary *bp)
+{
+ return erts_mk_magic_ref_get_refc(hpp, ohp, bp, NULL);
+}
+
ERTS_GLB_INLINE Binary *
erts_magic_ref2bin(Eterm mref)
{
diff --git a/erts/emulator/beam/erl_node_tables.c b/erts/emulator/beam/erl_node_tables.c
index b8c36f4ecd..3c806944eb 100644
--- a/erts/emulator/beam/erl_node_tables.c
+++ b/erts/emulator/beam/erl_node_tables.c
@@ -394,10 +394,13 @@ erts_build_dhandle(Eterm **hpp, ErlOffHeap* ohp,
{
Binary *bin = ErtsDistEntry2Bin(dep);
Eterm mref, dhandle;
+ erts_aint_t refc;
ASSERT(bin);
ASSERT(ERTS_MAGIC_BIN_DESTRUCTOR(bin) == erts_dist_entry_destructor);
- erts_refc_inc_if(&bin->intern.refc, 0, 0); /* inc for pending delete */
- mref = erts_mk_magic_ref(hpp, ohp, bin);
+ mref = erts_mk_magic_ref_get_refc(hpp, ohp, bin, &refc);
+ if (refc < 2) {
+ erts_refc_inc(&bin->intern.refc, 2); /* inc for pending delete */
+ }
dhandle = TUPLE2(*hpp, make_small(conn_id), mref);
*hpp += 3;
return dhandle;
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index 25e6ea89c8..2b8f69b2b9 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -61,6 +61,7 @@
bad_dist_ext_connection_id/1,
bad_dist_ext_size/1,
start_epmd_false/1, no_epmd/1, epmd_module/1,
+ dist_entry_refc_race/1,
huge_iovec/1]).
%% Internal exports.
@@ -69,6 +70,7 @@
optimistic_dflags_echo/0, optimistic_dflags_sender/1,
roundtrip/1, bounce/1, do_dist_auto_connect/1, inet_rpc_server/1,
dist_parallel_sender/3, dist_parallel_receiver/0,
+ derr_run/1,
dist_evil_parallel_receiver/0]).
%% epmd_module exports
@@ -89,6 +91,7 @@ all() ->
dist_parallel_send, atom_roundtrip, unicode_atom_roundtrip,
contended_atom_cache_entry, contended_unicode_atom_cache_entry,
bad_dist_structure, {group, bad_dist_ext},
+ dist_entry_refc_race,
start_epmd_false, no_epmd, epmd_module,
huge_iovec].
@@ -2123,6 +2126,48 @@ address_please(_Name, _Address, _AddressFamily) ->
mk_rand_bin(N-1, [rand:uniform(256) - 1 | Data]).
+%% Try provoke DistEntry refc bugs (OTP-17513).
+dist_entry_refc_race(_Config) ->
+ {ok, Node} = start_node(dist_entry_refc_race, "+zdntgc 1"),
+ Pid = spawn_link(Node, ?MODULE, derr_run, [self()]),
+ {Pid, done} = receive M -> M end,
+ stop_node(Node),
+ ok.
+
+derr_run(Papa) ->
+ inet_db:set_lookup([file]), % make connection attempt fail fast
+ NScheds = erlang:system_info(schedulers_online),
+ SeqList = lists:seq(1, 25 * NScheds),
+ Nodes = [list_to_atom("none@host" ++ integer_to_list(Seq))
+ || Seq <- SeqList],
+ Self = self(),
+ Pids = [spawn_link(fun () -> derr_sender(Self, Nodes) end)
+ || _ <- SeqList],
+ derr_count(1, 8000),
+ [begin unlink(P), exit(P,kill) end || P <- Pids],
+ Papa ! {self(), done},
+ ok.
+
+derr_count(Max, Max) ->
+ done;
+derr_count(N, Max) ->
+ receive
+ count -> ok
+ end,
+ case N rem 1000 of
+ 0 ->
+ io:format("Total attempts: ~bk~n", [N div 1000]);
+ _ -> ok
+ end,
+ derr_count(N+1, Max).
+
+
+derr_sender(Main, Nodes) ->
+ [{none, Node} ! msg || Node <- Nodes],
+ Main ! count,
+ derr_sender(Main, Nodes).
+
+
%%% Utilities
timestamp() ->
--
2.26.2