File 6472-erts-Fix-decode-of-BINARY_EXT-and-BIT_BINARY_EXT-whe.patch of Package erlang
From ee16427b16fbdc4d8b5f08bd7ef208f0f9d14421 Mon Sep 17 00:00:00 2001
From: Mikael Pettersson <mikpelinux@gmail.com>
Date: Sat, 29 Oct 2022 15:20:07 +0200
Subject: [PATCH 2/2] erts: Fix decode of BINARY_EXT and BIT_BINARY_EXT when
size >= 2Gb
Co-authored-by: Sverker Eriksson <sverker@erlang.org>
---
erts/emulator/beam/erl_binary.h | 19 +++----
erts/emulator/beam/external.c | 82 +++++++++++++++++------------
erts/emulator/beam/sys.h | 2 +
erts/emulator/test/binary_SUITE.erl | 19 +++++++
4 files changed, 79 insertions(+), 43 deletions(-)
diff --git a/erts/emulator/beam/erl_binary.h b/erts/emulator/beam/erl_binary.h
index 0e26688e2b..6482e0bcf1 100644
--- a/erts/emulator/beam/erl_binary.h
+++ b/erts/emulator/beam/erl_binary.h
@@ -328,6 +328,16 @@ ERTS_GLB_INLINE Binary *erts_create_magic_indirection(int (*destructor)(Binary *
ERTS_GLB_INLINE erts_atomic_t *erts_binary_to_magic_indirection(Binary *bp);
ERTS_GLB_INLINE erts_atomic_t *erts_binary_to_magic_indirection(Binary *bp);
+/* A binary's size in bits must fit into a word for matching to work. We used
+ * to allow creating larger binaries than this, but they acted really strangely
+ * in Erlang code and were pretty much only usable in drivers and NIFs.
+ *
+ * This check also ensures, indirectly, that there won't be an overflow when
+ * the size is bumped by CHICKEN_PAD and the binary struct itself. */
+#define IS_BINARY_SIZE_OK(BYTE_SIZE) \
+ ERTS_LIKELY(BYTE_SIZE <= ERTS_UWORD_MAX / CHAR_BIT)
+
+
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
#include <stddef.h> /* offsetof */
@@ -352,15 +362,6 @@ erts_free_aligned_binary_bytes(byte* buf)
erts_free_aligned_binary_bytes_extra(buf,ERTS_ALC_T_TMP);
}
-/* A binary's size in bits must fit into a word for matching to work. We used
- * to allow creating larger binaries than this, but they acted really strangely
- * in Erlang code and were pretty much only usable in drivers and NIFs.
- *
- * This check also ensures, indirectly, that there won't be an overflow when
- * the size is bumped by CHICKEN_PAD and the binary struct itself. */
-#define IS_BINARY_SIZE_OK(BYTE_SIZE) \
- ERTS_LIKELY(BYTE_SIZE <= ERTS_UWORD_MAX / CHAR_BIT)
-
/* Explicit extra bytes allocated to counter buggy drivers.
** These extra bytes where earlier (< R13B04) added by an alignment-bug
** in this code. Do we dare remove this in some major release (R14?) maybe?
diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index 1d1c473ab9..63d7d32487 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -4474,19 +4474,21 @@ dec_term_atom_common:
}
case BINARY_EXT:
{
- n = get_int32(ep);
+ Uint32 nu = get_uint32(ep);
ep += 4;
- if ((unsigned)n <= ERL_ONHEAP_BIN_LIMIT) {
+ ASSERT(IS_BINARY_SIZE_OK(nu));
+
+ if (nu <= ERL_ONHEAP_BIN_LIMIT) {
ErlHeapBin* hb = (ErlHeapBin *) hp;
- hb->thing_word = header_heap_bin(n);
- hb->size = n;
- hp += heap_bin_size(n);
- sys_memcpy(hb->data, ep, n);
+ hb->thing_word = header_heap_bin(nu);
+ hb->size = nu;
+ hp += heap_bin_size(nu);
+ sys_memcpy(hb->data, ep, nu);
*objp = make_binary(hb);
} else if (edep && edep->data && edep->data->binp &&
- n > (edep->data->binp->orig_size / 4)) {
+ nu > (edep->data->binp->orig_size / 4)) {
/* If we decode a refc binary from a distribution data
entry we know that it is a refc binary to begin with
so we just increment it and use the reference. This
@@ -4498,37 +4500,39 @@ dec_term_atom_common:
Binary* bptr = edep->data->binp;
erts_refc_inc(&bptr->intern.refc, 1);
pb->thing_word = HEADER_PROC_BIN;
- pb->size = n;
+ pb->size = nu;
pb->next = factory->off_heap->first;
factory->off_heap->first = (struct erl_off_heap_header*)pb;
pb->val = bptr;
pb->bytes = (byte*) ep;
ERTS_ASSERT((byte*)(bptr->orig_bytes) < ep &&
- ep+n <= (byte*)(bptr->orig_bytes+bptr->orig_size));
+ ep+nu <= (byte*)(bptr->orig_bytes+bptr->orig_size));
pb->flags = 0;
OH_OVERHEAD(factory->off_heap, pb->size / sizeof(Eterm));
hp += PROC_BIN_SIZE;
*objp = make_binary(pb);
} else {
- Binary* dbin = erts_bin_nrml_alloc(n);
+ Binary* dbin;
+
+ dbin = erts_bin_nrml_alloc(nu);
*objp = erts_build_proc_bin(factory->off_heap, hp, dbin);
hp += PROC_BIN_SIZE;
if (ctx) {
- int n_limit = reds * B2T_MEMCPY_FACTOR;
- if (n > n_limit) {
+ unsigned int n_limit = reds * B2T_MEMCPY_FACTOR;
+ if (nu > n_limit) {
ctx->state = B2TDecodeBinary;
- ctx->u.dc.remaining_n = n - n_limit;
+ ctx->u.dc.remaining_n = nu - n_limit;
ctx->u.dc.remaining_bytes = dbin->orig_bytes + n_limit;
- n = n_limit;
+ nu = n_limit;
reds = 0;
}
else
- reds -= n / B2T_MEMCPY_FACTOR;
+ reds -= nu / B2T_MEMCPY_FACTOR;
}
- sys_memcpy(dbin->orig_bytes, ep, n);
+ sys_memcpy(dbin->orig_bytes, ep, nu);
}
- ep += n;
+ ep += nu;
break;
}
case BIT_BINARY_EXT:
@@ -4536,51 +4540,53 @@ dec_term_atom_common:
Eterm bin;
ErlSubBin* sb;
Uint bitsize;
+ Uint32 nu = get_uint32(ep);
+
+ ASSERT(IS_BINARY_SIZE_OK(nu));
- n = get_int32(ep);
bitsize = ep[4];
- if (((bitsize==0) != (n==0)) || bitsize > 8)
+ if (((bitsize==0) != (nu==0)) || bitsize > 8)
goto error;
ep += 5;
- if ((unsigned)n <= ERL_ONHEAP_BIN_LIMIT) {
+ if (nu <= ERL_ONHEAP_BIN_LIMIT) {
ErlHeapBin* hb = (ErlHeapBin *) hp;
- hb->thing_word = header_heap_bin(n);
- hb->size = n;
- sys_memcpy(hb->data, ep, n);
+ hb->thing_word = header_heap_bin(nu);
+ hb->size = nu;
+ sys_memcpy(hb->data, ep, nu);
bin = make_binary(hb);
- hp += heap_bin_size(n);
- ep += n;
+ hp += heap_bin_size(nu);
+ ep += nu;
} else {
- Binary* dbin = erts_bin_nrml_alloc(n);
- Uint n_copy = n;
+ Binary* dbin = erts_bin_nrml_alloc(nu);
+ Uint n_copy = nu;
bin = erts_build_proc_bin(factory->off_heap, hp, dbin);
hp += PROC_BIN_SIZE;
if (ctx) {
int n_limit = reds * B2T_MEMCPY_FACTOR;
- if (n > n_limit) {
+ if (nu > n_limit) {
ctx->state = B2TDecodeBinary;
- ctx->u.dc.remaining_n = n - n_limit;
+ ctx->u.dc.remaining_n = nu - n_limit;
ctx->u.dc.remaining_bytes = dbin->orig_bytes + n_limit;
n_copy = n_limit;
reds = 0;
}
else {
- reds -= n / B2T_MEMCPY_FACTOR;
+ reds -= nu / B2T_MEMCPY_FACTOR;
}
}
sys_memcpy(dbin->orig_bytes, ep, n_copy);
ep += n_copy;
}
- if (bitsize == 8 || n == 0) {
+ if (bitsize == 8 || nu == 0) {
*objp = bin;
} else {
sb = (ErlSubBin *)hp;
sb->thing_word = HEADER_SUB_BIN;
sb->orig = bin;
- sb->size = n - 1;
+ sb->size = nu - 1;
sb->bitsize = bitsize;
sb->bitoffs = 0;
sb->offs = 0;
@@ -5605,7 +5611,11 @@ init_done:
break;
case BINARY_EXT:
CHKSIZE(4);
- n = get_int32(ep);
+ n = get_uint32(ep);
+#if defined(ARCH_32)
+ if (!IS_BINARY_SIZE_OK(n))
+ goto error;
+#endif
SKIP2(n, 4);
if (n <= ERL_ONHEAP_BIN_LIMIT) {
heap_size += heap_bin_size(n);
@@ -5616,7 +5626,11 @@ init_done:
case BIT_BINARY_EXT:
{
CHKSIZE(5);
- n = get_int32(ep);
+ n = get_uint32(ep);
+#if defined(ARCH_32)
+ if (!IS_BINARY_SIZE_OK(n))
+ goto error;
+#endif
SKIP2(n, 5);
if (n <= ERL_ONHEAP_BIN_LIMIT) {
heap_size += heap_bin_size(n) + ERL_SUB_BIN_SIZE;
diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl
index 49d2dfb983..c444b80fc1 100644
--- a/erts/emulator/test/binary_SUITE.erl
+++ b/erts/emulator/test/binary_SUITE.erl
@@ -65,6 +65,7 @@
bad_term_to_binary/1,
bad_binary_to_term_2/1,safe_binary_to_term2/1,
bad_binary_to_term/1, bad_terms/1, more_bad_terms/1,
+ big_binary_to_term/1,
otp_5484/1,otp_5933/1,
ordering/1,unaligned_order/1,gc_test/1,
bit_sized_binary_sizes/1,
@@ -93,6 +94,7 @@ all() ->
b2t_used_big,
bad_binary_to_term_2, safe_binary_to_term2,
bad_binary_to_term, bad_terms, t_hash, bad_size,
+ big_binary_to_term,
sub_bin_copy, bad_term_to_binary, t2b_system_limit,
term_to_iovec, more_bad_terms,
otp_5484, otp_5933,
@@ -950,6 +952,23 @@ safe_binary_to_term2(Config) when is_list(Config) ->
bad_bin_to_term(BadExtFun, [safe]),
ok.
+%% OTP-18306 Decode binary/bitstring with size >= 2Gbyte
+big_binary_to_term(Config) ->
+ run_when_enough_resources(
+ fun() ->
+ Bin = binary:copy(<<0>>, 2 * 1024 * 1024 * 1024),
+ big_binary_roundtrip(Bin),
+ erlang:garbage_collect(),
+ <<_:1, BitStr/bits>> = Bin,
+ big_binary_roundtrip(BitStr),
+ ok
+ end).
+
+big_binary_roundtrip(Bin) ->
+ Bin = erlang:binary_to_term(erlang:term_to_binary(Bin)),
+ ok.
+
+
%% Tests bad input to binary_to_term/1.
bad_terms(Config) when is_list(Config) ->
--
2.35.3