Skip to content

Commit

Permalink
Merge branch 'john/erts/fix-iovec-unaligned-binaries/OTP-14921' into …
Browse files Browse the repository at this point in the history
…maint
  • Loading branch information
jhogberg committed Feb 19, 2018
2 parents b64db2a + c47c8ed commit 474b2ef
Show file tree
Hide file tree
Showing 4 changed files with 144 additions and 80 deletions.
31 changes: 23 additions & 8 deletions erts/emulator/beam/erl_io_queue.c
Expand Up @@ -801,12 +801,11 @@ static Eterm iol2v_make_sub_bin(iol2v_state_t *state, Eterm bin_term,
ERTS_GET_REAL_BIN(bin_term, orig_pb_term,
byte_offset, bit_offset, bit_size);

(void)bit_offset;
(void)bit_size;
ASSERT(bit_size == 0);

sb->thing_word = HEADER_SUB_BIN;
sb->bitoffs = bit_offset;
sb->bitsize = 0;
sb->bitoffs = 0;
sb->orig = orig_pb_term;
sb->is_writable = 0;

Expand Down Expand Up @@ -984,7 +983,7 @@ static int iol2v_append_binary(iol2v_state_t *state, Eterm bin_term) {
parent_header = binary_val(parent_binary);
binary_size = binary_size(bin_term);

if (bit_offset != 0 || bit_size != 0) {
if (bit_size != 0) {
return 0;
} else if (binary_size == 0) {
state->bytereds_spent += 1;
Expand Down Expand Up @@ -1026,8 +1025,16 @@ static int iol2v_append_binary(iol2v_state_t *state, Eterm bin_term) {
* then just copy it into the accumulator. */
iol2v_expand_acc(state, binary_size);

sys_memcpy(&(state->acc)->orig_bytes[state->acc_size],
binary_data, binary_size);
if (ERTS_LIKELY(bit_offset == 0)) {
sys_memcpy(&(state->acc)->orig_bytes[state->acc_size],
binary_data, binary_size);
} else {
ASSERT(binary_size <= ERTS_UWORD_MAX / 8);

erts_copy_bits(binary_data, bit_offset, 1,
(byte*)&(state->acc)->orig_bytes[state->acc_size], 0, 1,
binary_size * 8);
}

state->acc_size += binary_size;
} else {
Expand All @@ -1038,8 +1045,16 @@ static int iol2v_append_binary(iol2v_state_t *state, Eterm bin_term) {

iol2v_expand_acc(state, spill);

sys_memcpy(&(state->acc)->orig_bytes[state->acc_size],
binary_data, spill);
if (ERTS_LIKELY(bit_offset == 0)) {
sys_memcpy(&(state->acc)->orig_bytes[state->acc_size],
binary_data, spill);
} else {
ASSERT(binary_size <= ERTS_UWORD_MAX / 8);

erts_copy_bits(binary_data, bit_offset, 1,
(byte*)&(state->acc)->orig_bytes[state->acc_size], 0, 1,
spill * 8);
}

state->acc_size += spill;

Expand Down
124 changes: 71 additions & 53 deletions erts/emulator/beam/erl_nif.c
Expand Up @@ -3396,8 +3396,8 @@ typedef struct {
Eterm sublist_start;
Eterm sublist_end;

UWord offheap_size;
UWord onheap_size;
UWord referenced_size;
UWord copied_size;

UWord iovec_len;
} iovec_slice_t;
Expand All @@ -3407,16 +3407,16 @@ static int examine_iovec_term(Eterm list, UWord max_length, iovec_slice_t *resul

result->sublist_start = list;
result->sublist_length = 0;
result->offheap_size = 0;
result->onheap_size = 0;
result->referenced_size = 0;
result->copied_size = 0;
result->iovec_len = 0;

lookahead = result->sublist_start;

while (is_list(lookahead)) {
Eterm *binary_header, binary;
UWord byte_size;
Eterm binary;
Eterm *cell;
UWord size;

cell = list_val(lookahead);
binary = CAR(cell);
Expand All @@ -3425,35 +3425,36 @@ static int examine_iovec_term(Eterm list, UWord max_length, iovec_slice_t *resul
return 0;
}

size = binary_size(binary);
binary_header = binary_val(binary);
byte_size = binary_size(binary);

if (size > 0) {
/* If we're a sub-binary we'll need to check our underlying binary
* to determine whether we're on-heap or not. */
if (thing_subtag(*binary_header) == SUB_BINARY_SUBTAG) {
ErlSubBin *sb = (ErlSubBin*)binary_header;
if (byte_size > 0) {
int bit_offset, bit_size;
Eterm parent_binary;
UWord byte_offset;

/* Reject bitstrings */
if((sb->bitoffs + sb->bitsize) > 0) {
return 0;
}
int requires_copying;

ASSERT(size <= binary_size(sb->orig));
binary_header = binary_val(sb->orig);
ERTS_GET_REAL_BIN(binary, parent_binary, byte_offset,
bit_offset, bit_size);

(void)byte_offset;

if (bit_size != 0) {
return 0;
}

if (thing_subtag(*binary_header) == HEAP_BINARY_SUBTAG) {
ASSERT(size <= ERL_ONHEAP_BIN_LIMIT);
/* If we're unaligned or an on-heap binary we'll need to copy
* ourselves over to a temporary buffer. */
requires_copying = (bit_offset != 0) ||
thing_subtag(*binary_val(parent_binary)) == HEAP_BINARY_SUBTAG;

result->iovec_len += 1;
result->onheap_size += size;
if (requires_copying) {
result->copied_size += byte_size;
} else {
ASSERT(thing_subtag(*binary_header) == REFC_BINARY_SUBTAG);

result->iovec_len += 1 + size / MAX_SYSIOVEC_IOVLEN;
result->offheap_size += size;
result->referenced_size += byte_size;
}

result->iovec_len += 1 + byte_size / MAX_SYSIOVEC_IOVLEN;
}

result->sublist_length += 1;
Expand All @@ -3473,7 +3474,9 @@ static int examine_iovec_term(Eterm list, UWord max_length, iovec_slice_t *resul
return 1;
}

static void inspect_raw_binary_data(Eterm binary, ErlNifBinary *result) {
static void marshal_iovec_binary(Eterm binary, ErlNifBinary *copy_buffer,
UWord *copy_offset, ErlNifBinary *result) {

Eterm *parent_header;
Eterm parent_binary;

Expand All @@ -3484,6 +3487,8 @@ static void inspect_raw_binary_data(Eterm binary, ErlNifBinary *result) {

ERTS_GET_REAL_BIN(binary, parent_binary, byte_offset, bit_offset, bit_size);

ASSERT(bit_size == 0);

parent_header = binary_val(parent_binary);

result->size = binary_size(binary);
Expand All @@ -3510,45 +3515,58 @@ static void inspect_raw_binary_data(Eterm binary, ErlNifBinary *result) {
result->data = &((unsigned char*)&hb->data)[byte_offset];
result->ref_bin = NULL;
}

/* If this isn't an *aligned* refc binary, copy its contents to the buffer
* and reference that instead. */

if (result->ref_bin == NULL || bit_offset != 0) {
ASSERT(result->size <= (copy_buffer->size - *copy_offset));

if (bit_offset == 0) {
sys_memcpy(&copy_buffer->data[*copy_offset],
result->data, result->size);
} else {
erts_copy_bits(result->data, bit_offset, 1,
(byte*)&copy_buffer->data[*copy_offset], 0, 1,
result->size * 8);
}

result->data = &copy_buffer->data[*copy_offset];
result->ref_bin = copy_buffer->ref_bin;

*copy_offset += result->size;
}
}

static int fill_iovec_with_slice(ErlNifEnv *env,
iovec_slice_t *slice,
ErlNifIOVec *iovec) {
UWord onheap_offset, iovec_idx;
ErlNifBinary onheap_data;
UWord copy_offset, iovec_idx;
ErlNifBinary copy_buffer;
Eterm sublist_iterator;

/* Set up a common refc binary for all on-heap binaries. */
if (slice->onheap_size > 0) {
if (!enif_alloc_binary(slice->onheap_size, &onheap_data)) {
/* Set up a common refc binary for all on-heap and unaligned binaries. */
if (slice->copied_size > 0) {
if (!enif_alloc_binary(slice->copied_size, &copy_buffer)) {
return 0;
}
} else {
#ifdef DEBUG
copy_buffer.data = NULL;
copy_buffer.size = 0;
#endif
}

sublist_iterator = slice->sublist_start;
onheap_offset = 0;
copy_offset = 0;
iovec_idx = 0;

while (sublist_iterator != slice->sublist_end) {
ErlNifBinary raw_data;
Eterm *cell;

cell = list_val(sublist_iterator);
inspect_raw_binary_data(CAR(cell), &raw_data);

/* If this isn't a refc binary, copy its contents to the onheap buffer
* and reference that instead. */
if (raw_data.size > 0 && raw_data.ref_bin == NULL) {
ASSERT(onheap_offset < onheap_data.size);
ASSERT(slice->onheap_size > 0);

sys_memcpy(&onheap_data.data[onheap_offset],
raw_data.data, raw_data.size);

raw_data.data = &onheap_data.data[onheap_offset];
raw_data.ref_bin = onheap_data.ref_bin;
}
marshal_iovec_binary(CAR(cell), &copy_buffer, &copy_offset, &raw_data);

while (raw_data.size > 0) {
UWord chunk_len = MIN(raw_data.size, MAX_SYSIOVEC_IOVLEN);
Expand Down Expand Up @@ -3579,16 +3597,16 @@ static int fill_iovec_with_slice(ErlNifEnv *env,
erts_refc_inc(&refc_binary->intern.refc, 1);
}

if (slice->onheap_size > 0) {
if (slice->copied_size > 0) {
/* Transfer ownership to the iovec; we've taken references to it in
* the above loop. */
enif_release_binary(&onheap_data);
enif_release_binary(&copy_buffer);
}
} else {
if (slice->onheap_size > 0) {
if (slice->copied_size > 0) {
/* Attach the binary to our environment and let the GC take care of
* it after returning. */
enif_make_binary(env, &onheap_data);
enif_make_binary(env, &copy_buffer);
}
}

Expand Down Expand Up @@ -3635,7 +3653,7 @@ static int create_iovec_from_slice(ErlNifEnv *env,
iovec->flags = 0;
}

iovec->size = slice->offheap_size + slice->onheap_size;
iovec->size = slice->referenced_size + slice->copied_size;
iovec->iovcnt = slice->iovec_len;

if(!fill_iovec_with_slice(env, slice, iovec)) {
Expand Down
39 changes: 22 additions & 17 deletions erts/emulator/test/iovec_SUITE.erl
Expand Up @@ -25,7 +25,7 @@
-export([integer_lists/1, binary_lists/1, empty_lists/1, empty_binary_lists/1,
mixed_lists/1, improper_lists/1, illegal_lists/1, cons_bomb/1,
sub_binary_lists/1, iolist_to_iovec_idempotence/1,
iolist_to_iovec_correctness/1]).
iolist_to_iovec_correctness/1, unaligned_sub_binaries/1]).

-include_lib("common_test/include/ct.hrl").

Expand All @@ -36,7 +36,8 @@ suite() ->
all() ->
[integer_lists, binary_lists, empty_lists, empty_binary_lists, mixed_lists,
sub_binary_lists, illegal_lists, improper_lists, cons_bomb,
iolist_to_iovec_idempotence, iolist_to_iovec_correctness].
iolist_to_iovec_idempotence, iolist_to_iovec_correctness,
unaligned_sub_binaries].

init_per_suite(Config) ->
Config.
Expand Down Expand Up @@ -78,7 +79,7 @@ illegal_lists(Config) when is_list(Config) ->
BitStrs = gen_variations(["gurka", <<1:1>>, "gaffel"]),
BadInts = gen_variations(["gurka", 890, "gaffel"]),
Atoms = gen_variations([gurka, "gaffel"]),
BadTails = [["test" | 0], ["gurka", gaffel]],
BadTails = [["test" | 0], ["gurka" | gaffel], ["gaffel" | <<1:1>>]],

Variations =
BitStrs ++ BadInts ++ Atoms ++ BadTails,
Expand All @@ -98,14 +99,7 @@ cons_bomb(Config) when is_list(Config) ->
BinBase = gen_variations([<<I:8>> || I <- lists:seq(1, 255)]),
MixBase = gen_variations([<<12, 45, 78>>, lists:seq(1, 255)]),

Rounds =
case system_mem_size() of
Mem when Mem >= (16 bsl 30) -> 32;
Mem when Mem >= (3 bsl 30) -> 28;
_ -> 20
end,

Variations = gen_variations([IntBase, BinBase, MixBase], Rounds),
Variations = gen_variations([IntBase, BinBase, MixBase], 16),
equivalence_test(fun erlang:iolist_to_iovec/1, Variations).

iolist_to_iovec_idempotence(Config) when is_list(Config) ->
Expand All @@ -130,6 +124,15 @@ iolist_to_iovec_correctness(Config) when is_list(Config) ->
true = is_iolist_equal(Optimized, Variations),
ok.

unaligned_sub_binaries(Config) when is_list(Config) ->
UnalignedBins = [gen_unaligned_binary(I) || I <- lists:seq(32, 4 bsl 10, 512)],
UnalignedVariations = gen_variations(UnalignedBins),

Optimized = erlang:iolist_to_iovec(UnalignedVariations),

true = is_iolist_equal(Optimized, UnalignedVariations),
ok.

illegality_test(Fun, Variations) ->
[{'EXIT',{badarg, _}} = (catch Fun(Variation)) || Variation <- Variations],
ok.
Expand All @@ -145,11 +148,18 @@ equivalence_test(Fun, [Head | _] = Variations) ->
is_iolist_equal(A, B) ->
iolist_to_binary(A) =:= iolist_to_binary(B).

gen_unaligned_binary(Size) ->
Bin0 = << <<I>> || I <- lists:seq(1, Size) >>,
<<0:3,Bin:Size/binary,31:5>> = id(<<0:3,Bin0/binary,31:5>>),
Bin.

id(I) -> I.

%% Generates a bunch of lists whose contents will be equal to Base repeated a
%% few times. The lists only differ by their structure, so their reduction to
%% a simpler format should yield the same result.
gen_variations(Base) ->
gen_variations(Base, 16).
gen_variations(Base, 12).
gen_variations(Base, N) ->
[gen_flat_list(Base, N),
gen_nested_list(Base, N),
Expand All @@ -169,8 +179,3 @@ gen_nasty_list_1([Head | Base], Result) when is_list(Head) ->
gen_nasty_list_1(Base, [[Result], [gen_nasty_list_1(Head, [])]]);
gen_nasty_list_1([Head | Base], Result) ->
gen_nasty_list_1(Base, [[Result], [Head]]).

system_mem_size() ->
application:ensure_all_started(os_mon),
{Tot,_Used,_} = memsup:get_memory_data(),
Tot.

0 comments on commit 474b2ef

Please sign in to comment.