summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorErlang/OTP <otp@erlang.org>2022-07-12 12:25:32 +0200
committerErlang/OTP <otp@erlang.org>2022-07-12 12:25:32 +0200
commit96abc06dd91611b5de50a3e6a1ed4c983a171883 (patch)
treed7eea51b3a02e323f77f96c9a113d73c786bfaac
parent8e9201679129a42c9a2a78940dae83a058be68f2 (diff)
parent46cafed2c31b8a64df3da7fc088f8875b45e2ace (diff)
downloaderlang-96abc06dd91611b5de50a3e6a1ed4c983a171883.tar.gz
Merge branch 'sverker/23/fix-hopeful-fun-size-encoding/OTP-18104' into maint-23
* sverker/23/fix-hopeful-fun-size-encoding/OTP-18104: erl_interface: Improve ei_accept_SUITE:hopeful_random erts: Fix bug in bit string fallback encoding erts: Fix size encoding of fun containing off-heap binaries erts: Fix fallback combo bug on pending connection erl_interface: Add test runner rr option erl_interface: Test receiving fun with hopeful environment erts: Fix encoding of NEW_FUN_EXT Size field for pending connection
-rw-r--r--erts/emulator/beam/dist.c13
-rw-r--r--erts/emulator/beam/dist.h2
-rw-r--r--erts/emulator/beam/erl_bif_info.c13
-rw-r--r--erts/emulator/beam/external.c113
-rw-r--r--erts/emulator/beam/external.h1
-rw-r--r--erts/emulator/test/distribution_SUITE.erl72
-rw-r--r--lib/erl_interface/test/all_SUITE_data/ei_runner.h1
-rw-r--r--lib/erl_interface/test/ei_accept_SUITE.erl253
-rw-r--r--lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_test.c19
-rw-r--r--lib/erl_interface/test/runner.erl15
10 files changed, 443 insertions, 59 deletions
diff --git a/erts/emulator/beam/dist.c b/erts/emulator/beam/dist.c
index 3ab06a0a91..0431763449 100644
--- a/erts/emulator/beam/dist.c
+++ b/erts/emulator/beam/dist.c
@@ -179,7 +179,7 @@ static char *erts_dop_to_string(enum dop dop) {
int erts_is_alive; /* System must be blocked on change */
int erts_dist_buf_busy_limit;
-int erts_dflags_test_remove_hopefull_flags;
+Uint64 erts_dflags_test_remove_hopefull_flags;
Export spawn_request_yield_export;
@@ -5131,17 +5131,18 @@ BIF_RETTYPE erts_internal_get_dflags_0(BIF_ALIST_0)
{
if (erts_dflags_test_remove_hopefull_flags) {
/* For internal emulator tests only! */
+ const Uint64 mask = ~erts_dflags_test_remove_hopefull_flags;
Eterm *hp, **hpp = NULL;
Uint sz = 0, *szp = &sz;
Eterm res;
while (1) {
res = erts_bld_tuple(hpp, szp, 6,
am_erts_dflags,
- erts_bld_uint64(hpp, szp, DFLAG_DIST_DEFAULT & ~DFLAG_DIST_HOPEFULLY),
- erts_bld_uint64(hpp, szp, DFLAG_DIST_MANDATORY & ~DFLAG_DIST_HOPEFULLY),
- erts_bld_uint64(hpp, szp, DFLAG_DIST_ADDABLE & ~DFLAG_DIST_HOPEFULLY),
- erts_bld_uint64(hpp, szp, DFLAG_DIST_REJECTABLE & ~DFLAG_DIST_HOPEFULLY),
- erts_bld_uint64(hpp, szp, DFLAG_DIST_STRICT_ORDER & ~DFLAG_DIST_HOPEFULLY));
+ erts_bld_uint64(hpp, szp, DFLAG_DIST_DEFAULT & mask),
+ erts_bld_uint64(hpp, szp, DFLAG_DIST_MANDATORY & mask),
+ erts_bld_uint64(hpp, szp, DFLAG_DIST_ADDABLE & mask),
+ erts_bld_uint64(hpp, szp, DFLAG_DIST_REJECTABLE & mask),
+ erts_bld_uint64(hpp, szp, DFLAG_DIST_STRICT_ORDER & mask));
if (hpp) {
ASSERT(is_value(res));
return res;
diff --git a/erts/emulator/beam/dist.h b/erts/emulator/beam/dist.h
index cdc7031476..813734b3cc 100644
--- a/erts/emulator/beam/dist.h
+++ b/erts/emulator/beam/dist.h
@@ -204,7 +204,7 @@ extern int erts_is_alive;
#define ERTS_DIST_CTRL_OPT_GET_SIZE ((Uint32) (1 << 0))
/* for emulator internal testing... */
-extern int erts_dflags_test_remove_hopefull_flags;
+extern Uint64 erts_dflags_test_remove_hopefull_flags;
#ifdef DEBUG
#define ERTS_DBG_CHK_NO_DIST_LNK(D, R, L) \
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index bf67cf3584..810761a530 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -4919,24 +4919,21 @@ BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
BIF_RET(copy);
}
else if (ERTS_IS_ATOM_STR("remove_hopefull_dflags", BIF_ARG_1)) {
- int old_val, new_val;
+ Uint64 new_val;
- switch (BIF_ARG_2) {
- case am_true: new_val = !0; break;
- case am_false: new_val = 0; break;
- default: BIF_ERROR(BIF_P, BADARG); break;
- }
+ if (!term_to_Uint64(BIF_ARG_2, &new_val)
+ || (new_val & ~DFLAG_DIST_HOPEFULLY))
+ BIF_ERROR(BIF_P, BADARG);
erts_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
erts_thr_progress_block();
- old_val = erts_dflags_test_remove_hopefull_flags;
erts_dflags_test_remove_hopefull_flags = new_val;
erts_thr_progress_unblock();
erts_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
- BIF_RET(old_val ? am_true : am_false);
+ BIF_RET(am_ok);
}
else if (ERTS_IS_ATOM_STR("code_write_permission", BIF_ARG_1)) {
/*
diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index 3f40dcfca3..045fee5b06 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -125,12 +125,15 @@ static ErtsExtSzRes encode_size_struct_int(TTBSizeContext*, ErtsAtomCacheMap *ac
static Export binary_to_term_trap_export;
static BIF_RETTYPE binary_to_term_trap_1(BIF_ALIST_1);
static Sint transcode_dist_obuf(ErtsDistOutputBuf*, DistEntry*, Uint64 dflags, Sint reds);
+static byte *begin_hopefull_data(TTBEncodeContext *ctx, byte *ep);
+static byte *end_hopefull_data(TTBEncodeContext *ctx, byte *ep, Uint fallback_size);
static byte *hopefull_bit_binary(TTBEncodeContext* ctx, byte **epp, Binary *pb_val, Eterm pb_term,
byte *bytes, byte bitoffs, byte bitsize, Uint sz);
static void hopefull_export(TTBEncodeContext* ctx, byte **epp, Export* exp, Uint32 dflags,
struct erl_off_heap_header** off_heap);
static void store_in_vec(TTBEncodeContext *ctx, byte *ep, Binary *ohbin, Eterm ohpb,
byte *ohp, Uint ohsz);
+static Uint32 calc_iovec_fun_size(SysIOVec* iov, Uint32 fun_high_ix, byte* size_p);
void erts_init_external(void) {
erts_init_trap_export(&term_to_binary_trap_export,
@@ -3098,8 +3101,47 @@ enc_term_int(TTBEncodeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj, byte* ep,
break;
case ENC_PATCH_FUN_SIZE:
{
- byte* size_p = (byte *) obj;
- put_int32(ep - size_p, size_p);
+ byte* size_p = (byte *) obj;
+ Sint32 fun_sz;
+
+ if (use_iov && !ErtsInArea(size_p, ctx->cptr, ep - ctx->cptr)) {
+ ASSERT(ctx->vlen > 0);
+ fun_sz = (ep - ctx->cptr)
+ + calc_iovec_fun_size(ctx->iov, ctx->vlen-1, size_p);
+
+ if (dflags & DFLAG_PENDING_CONNECT) {
+ /*
+ * Problem: The fun may contain hopefully encoded stuff
+ * in its environment. This makes the correct fun size
+ * may not be known until a final fallback transcoding
+ * has been done in transcode_dist_obuf().
+ */
+ ep = begin_hopefull_data(ctx, ep);
+ *ep++ = HOPEFUL_END_OF_FUN;
+ sys_memcpy(ep, &size_p, sizeof(size_p));
+ ep += sizeof(size_p);
+ ep = end_hopefull_data(ctx, ep, 0);
+ ASSERT(ctx->iov[ctx->vlen - 1].iov_len
+ == 1 + sizeof(size_p));
+ ASSERT(*(byte*)ctx->iov[ctx->vlen - 1].iov_base
+ == HOPEFUL_END_OF_FUN);
+ /*
+ * The HOPEFUL_END_OF_FUN iovec data entry encoded above
+ * contains no actual payload, only meta data to patch
+ * the correct fun size in transcode_dist_obuf().
+ * Therefor reset its iov_len to zero to avoid output as
+ * payload.
+ */
+ ctx->fragment_eiovs[ctx->frag_ix].size -= 1 + sizeof(size_p);
+ ctx->iov[ctx->vlen - 1].iov_len = 0;
+ }
+ }
+ else {
+ /* No iovec encoding or still in same iovec buffer as start
+ * of fun. Easy to calculate fun size. */
+ fun_sz = ep - size_p;
+ }
+ put_int32(fun_sz, size_p);
}
goto outer_loop;
case ENC_BIN_COPY: {
@@ -3606,6 +3648,7 @@ enc_term_int(TTBEncodeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj, byte* ep,
int ei;
ASSERT(dflags & DFLAG_NEW_FUN_TAGS);
+
*ep++ = NEW_FUN_EXT;
WSTACK_PUSH2(s, ENC_PATCH_FUN_SIZE,
(UWord) ep); /* Position for patching in size */
@@ -4967,7 +5010,8 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
}
#define LIST_TAIL_OP ((0 << _TAG_PRIMARY_SIZE) | TAG_PRIMARY_HEADER)
-#define TERM_ARRAY_OP(N) (((N) << _TAG_PRIMARY_SIZE) | TAG_PRIMARY_HEADER)
+#define PATCH_FUN_SIZE_OP ((1 << _TAG_PRIMARY_SIZE) | TAG_PRIMARY_HEADER)
+#define TERM_ARRAY_OP(N) (((N+1) << _TAG_PRIMARY_SIZE) | TAG_PRIMARY_HEADER)
#define TERM_ARRAY_OP_DEC(OP) ((OP) - (1 << _TAG_PRIMARY_SIZE))
@@ -5212,7 +5256,8 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
+ 1 /* 2 tuple size */
+ 1 /* BINARY_EXT */
+ 4 /* binary size */);
- trailing_result = (1 /* SMALL_INTEGER_EXT */
+ trailing_result = (1 /* trailing bits */
+ + 1 /* SMALL_INTEGER_EXT */
+ 1 /* bitsize */);
}
csz = result - ctx->last_result;
@@ -5248,6 +5293,7 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
during a pending connect. */
Uint csz = result - ctx->last_result;
ASSERT(dflags & DFLAG_BIT_BINARIES);
+ ASSERT(vlen >= 0);
/* potentially multiple elements leading up to binary */
vlen += (csz + MAX_SYSIOVEC_IOVLEN - 1)/MAX_SYSIOVEC_IOVLEN;
@@ -5284,6 +5330,10 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
ErlFunThing* funp = (ErlFunThing *) fun_val(obj);
ASSERT(dflags & DFLAG_NEW_FUN_TAGS);
+ if (dflags & DFLAG_PENDING_CONNECT) {
+ ASSERT(vlen >= 0);
+ WSTACK_PUSH(s, PATCH_FUN_SIZE_OP);
+ }
result += 20+1+1+4; /* New ID + Tag */
result += 4; /* Length field (number of free variables */
result += encode_size_struct2(acmp, funp->creator, dflags);
@@ -5315,6 +5365,7 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
* the hopefull index + hopefull encoding is larger...
*/
ASSERT(dflags & DFLAG_EXPORT_PTR_TAG);
+ ASSERT(vlen >= 0);
csz = tmp_result - ctx->last_result;
/* potentially multiple elements leading up to hopefull entry */
vlen += (csz/MAX_SYSIOVEC_IOVLEN + 1
@@ -5330,6 +5381,7 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
obj);
}
+ pop_next:
if (WSTACK_ISEMPTY(s)) {
break;
}
@@ -5347,6 +5399,19 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
}
break;
+ case PATCH_FUN_SIZE_OP: {
+ Uint csz;
+ ASSERT(vlen >= 0 && (dflags & DFLAG_PENDING_CONNECT));
+ csz = result - ctx->last_result;
+ /* potentially multiple elements leading up to hopefull entry */
+ vlen += (csz/MAX_SYSIOVEC_IOVLEN + 1
+ + 1); /* hopefull entry */
+ result += (4 /* hopefull index */
+ + 1 /* HOPEFUL_END_OF_FUN */
+ + sizeof(byte*)); /* size_p */
+ ctx->last_result = result;
+ goto pop_next;
+ }
case TERM_ARRAY_OP(1):
obj = *(Eterm*)WSTACK_POP(s);
break;
@@ -5781,6 +5846,29 @@ transcode_decode_state_destroy(ErtsTranscodeDecodeState *state)
erts_free(ERTS_ALC_T_TMP, state->hp);
}
+static Uint32
+calc_iovec_fun_size(SysIOVec* iov, Uint32 fun_high_ix, byte* size_p)
+{
+ Sint32 ix;
+ Uint32 fun_size = 0;
+
+ ASSERT(size_p[-1] == NEW_FUN_EXT);
+
+ /*
+ * Search backwards for start of fun while adding up its total byte size.
+ */
+ for (ix = fun_high_ix; ix >= 0; ix--) {
+ fun_size += iov[ix].iov_len;
+
+ if (ErtsInArea(size_p, iov[ix].iov_base, iov[ix].iov_len)) {
+ fun_size -= (size_p - (byte*)iov[ix].iov_base);
+ break;
+ }
+ }
+ ERTS_ASSERT(ix >= 0);
+ return fun_size;
+}
+
static
Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
DistEntry* dep,
@@ -6061,7 +6149,7 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
case EXPORT_EXT: {
byte *start_ep, *end_ep;
Eterm module, function;
- if (!(hopefull_flags & DFLAG_EXPORT_PTR_TAG))
+ if (dflags & DFLAG_EXPORT_PTR_TAG)
break;
/* Read original encoding... */
ep++;
@@ -6106,7 +6194,7 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
Uint bin_sz;
byte bitsize, epilog_byte;
ASSERT(hopefull_ix != ERTS_NO_HIX);
- if (!(hopefull_flags & DFLAG_BIT_BINARIES)) {
+ if (dflags & DFLAG_BIT_BINARIES) {
/* skip to epilog... */
hopefull_ix = new_hopefull_ix;
ep = (byte *) iov[hopefull_ix].iov_base;
@@ -6185,6 +6273,19 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
break;
}
+ case HOPEFUL_END_OF_FUN: {
+ byte* size_p;
+ Uint32 fun_sz;
+
+ ASSERT(iov[hopefull_ix].iov_len == 0);
+ ep++;
+ sys_memcpy(&size_p, ep, sizeof(size_p));
+
+ fun_sz = calc_iovec_fun_size(iov, hopefull_ix-1, size_p);
+ put_int32(fun_sz, size_p);
+ break;
+ }
+
default:
ERTS_INTERNAL_ERROR("Unexpected external tag");
break;
diff --git a/erts/emulator/beam/external.h b/erts/emulator/beam/external.h
index 937dc532f6..0a9b2133d5 100644
--- a/erts/emulator/beam/external.h
+++ b/erts/emulator/beam/external.h
@@ -61,6 +61,7 @@
#define DIST_FRAG_HEADER 'E'
#define DIST_FRAG_CONT 'F'
#define HOPEFUL_DATA 'H'
+#define HOPEFUL_END_OF_FUN 'Q'
#define ATOM_CACHE_REF 'R'
#define ATOM_INTERNAL_REF2 'I'
#define ATOM_INTERNAL_REF3 'K'
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index a885053eb3..1b76f3d3d9 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -30,6 +30,9 @@
-define(ATOM_UTF8_EXT, 118).
-define(SMALL_ATOM_UTF8_EXT, 119).
+-define(DFLAG_EXPORT_PTR_TAG, 16#200).
+-define(DFLAG_BIT_BINARIES, 16#400).
+
%% Tests distribution and the tcp driver.
-include_lib("common_test/include/ct.hrl").
@@ -2788,33 +2791,41 @@ address_please(_Name, _Address, _AddressFamily) ->
{ok, IP}.
hopefull_data_encoding(Config) when is_list(Config) ->
+
+ FallbackCombos = [A bor B || A <- [0, ?DFLAG_EXPORT_PTR_TAG],
+ B <- [0, ?DFLAG_BIT_BINARIES]],
+
+ [hopefull_data_encoding_do(FB) || FB <- FallbackCombos],
+ ok.
+
+
+hopefull_data_encoding_do(Fallback) ->
+ io:format("Fallback = 16#~.16B\n", [Fallback]),
+
MkHopefullData = fun(Ref,Pid) -> mk_hopefull_data(Ref,Pid) end,
- test_hopefull_data_encoding(Config, true, MkHopefullData),
- test_hopefull_data_encoding(Config, false, MkHopefullData),
+ test_hopefull_data_encoding(Fallback, MkHopefullData),
%% Test funs with hopefully encoded term in environment
MkBitstringInFunEnv = fun(_,_) -> [mk_fun_with_env(<<5:7>>)] end,
- test_hopefull_data_encoding(Config, true, MkBitstringInFunEnv),
- test_hopefull_data_encoding(Config, false, MkBitstringInFunEnv),
+ test_hopefull_data_encoding(Fallback, MkBitstringInFunEnv),
MkExpFunInFunEnv = fun(_,_) -> [mk_fun_with_env(fun a:a/0)] end,
- test_hopefull_data_encoding(Config, true, MkExpFunInFunEnv),
- test_hopefull_data_encoding(Config, false, MkExpFunInFunEnv),
+ test_hopefull_data_encoding(Fallback, MkExpFunInFunEnv),
ok.
mk_fun_with_env(Term) ->
fun() -> Term end.
-test_hopefull_data_encoding(Config, Fallback, MkDataFun) when is_list(Config) ->
+test_hopefull_data_encoding(Fallback, MkDataFun) ->
{ok, ProxyNode} = start_node(hopefull_data_normal),
{ok, BouncerNode} = start_node(hopefull_data_bouncer, "-hidden"),
case Fallback of
- false ->
+ 0 ->
ok;
- true ->
+ _ ->
rpc:call(BouncerNode, erts_debug, set_internal_state,
[available_internal_state, true]),
- false = rpc:call(BouncerNode, erts_debug, set_internal_state,
- [remove_hopefull_dflags, true])
+ ok = rpc:call(BouncerNode, erts_debug, set_internal_state,
+ [remove_hopefull_dflags, Fallback])
end,
Tester = self(),
R1 = make_ref(),
@@ -2846,19 +2857,19 @@ test_hopefull_data_encoding(Config, Fallback, MkDataFun) when is_list(Config) ->
receive
[R2, HData2] ->
case Fallback of
- false ->
+ 0 ->
HData = HData2;
- true ->
- check_hopefull_fallback_data(HData, HData2)
+ _ ->
+ check_hopefull_fallback_data(HData, HData2, Fallback)
end
end,
receive
[R3, HData3] ->
case Fallback of
- false ->
+ 0 ->
HData = HData3;
- true ->
- check_hopefull_fallback_data(HData, HData3)
+ _ ->
+ check_hopefull_fallback_data(HData, HData3, Fallback)
end
end,
unlink(Proxy),
@@ -2925,17 +2936,18 @@ mk_hopefull_data(BS) ->
[NewBs]
end, lists:seq(BSsz-32, BSsz-17))]).
-check_hopefull_fallback_data([], []) ->
+check_hopefull_fallback_data([], [], _) ->
ok;
-check_hopefull_fallback_data([X|Xs],[Y|Ys]) ->
- chk_hopefull_fallback(X, Y),
- check_hopefull_fallback_data(Xs,Ys).
+check_hopefull_fallback_data([X|Xs],[Y|Ys], FB) ->
+ chk_hopefull_fallback(X, Y, FB),
+ check_hopefull_fallback_data(Xs, Ys, FB).
-chk_hopefull_fallback(Binary, FallbackBinary) when is_binary(Binary) ->
+chk_hopefull_fallback(Binary, FallbackBinary, _) when is_binary(Binary) ->
Binary = FallbackBinary;
-chk_hopefull_fallback([BitStr], [{Bin, BitSize}]) when is_bitstring(BitStr) ->
- chk_hopefull_fallback(BitStr, {Bin, BitSize});
-chk_hopefull_fallback(BitStr, {Bin, BitSize}) when is_bitstring(BitStr) ->
+chk_hopefull_fallback([BitStr], [{Bin, BitSize}], FB) when is_bitstring(BitStr) ->
+ chk_hopefull_fallback(BitStr, {Bin, BitSize}, FB);
+chk_hopefull_fallback(BitStr, {Bin, BitSize}, FB) when is_bitstring(BitStr) ->
+ true = ((FB band ?DFLAG_BIT_BINARIES) =/= 0),
true = is_binary(Bin),
true = is_integer(BitSize),
true = BitSize > 0,
@@ -2946,20 +2958,22 @@ chk_hopefull_fallback(BitStr, {Bin, BitSize}) when is_bitstring(BitStr) ->
FallbackBitStr = list_to_bitstring([Head,<<IBits:BitSize>>]),
BitStr = FallbackBitStr,
ok;
-chk_hopefull_fallback(Func, {ModName, FuncName}) when is_function(Func) ->
+chk_hopefull_fallback(Func, {ModName, FuncName}, FB) when is_function(Func) ->
+ true = ((FB band ?DFLAG_EXPORT_PTR_TAG) =/= 0),
{M, F, _} = erlang:fun_info_mfa(Func),
M = ModName,
F = FuncName,
ok;
-chk_hopefull_fallback(Fun1, Fun2) when is_function(Fun1), is_function(Fun2) ->
+chk_hopefull_fallback(Fun1, Fun2, FB) when is_function(Fun1), is_function(Fun2) ->
+ %% Recursive diff of funs with their environments
FI1 = erlang:fun_info(Fun1),
FI2 = erlang:fun_info(Fun2),
{env, E1} = lists:keyfind(env, 1, FI1),
{env, E2} = lists:keyfind(env, 1, FI1),
- chk_hopefull_fallback(E1, E2),
+ chk_hopefull_fallback(E1, E2, FB),
assert_same(lists:keydelete(env, 1, FI1),
lists:keydelete(env, 1, FI2));
-chk_hopefull_fallback(A, B) ->
+chk_hopefull_fallback(A, B, _) ->
ok = assert_same(A,B).
assert_same(A,A) -> ok.
diff --git a/lib/erl_interface/test/all_SUITE_data/ei_runner.h b/lib/erl_interface/test/all_SUITE_data/ei_runner.h
index 6d6e0717e8..2b52225d33 100644
--- a/lib/erl_interface/test/all_SUITE_data/ei_runner.h
+++ b/lib/erl_interface/test/all_SUITE_data/ei_runner.h
@@ -54,6 +54,7 @@ void free_packet(char*);
#define fail(reason) do_fail(__FILE__, __LINE__, reason)
#define fail1(reason, a1) do_fail(__FILE__, __LINE__, reason, a1)
#define fail2(reason, a1, a2) do_fail(__FILE__, __LINE__, reason, a1, a2)
+#define fail3(reason, a1, a2, a3) do_fail(__FILE__, __LINE__, reason, a1, a2, a3)
#define report(ok) do_report(__FILE__, __LINE__, ok)
void do_report(char* file, int line, int ok);
diff --git a/lib/erl_interface/test/ei_accept_SUITE.erl b/lib/erl_interface/test/ei_accept_SUITE.erl
index 612d6e1b81..6ca1719088 100644
--- a/lib/erl_interface/test/ei_accept_SUITE.erl
+++ b/lib/erl_interface/test/ei_accept_SUITE.erl
@@ -26,23 +26,37 @@
-export([all/0, suite/0,
init_per_testcase/2,
- ei_accept/1, ei_threaded_accept/1,
+ ei_accept/1,
+ hopeful_random/1,
+ ei_threaded_accept/1,
monitor_ei_process/1]).
+%% Internals
+-export([id/1]).
+
-import(runner, [get_term/1,send_term/2]).
+
+-define(ERL_ONHEAP_BIN_LIMIT, 64).
+
suite() ->
[{ct_hooks,[ts_install_cth]},
{timetrap, {seconds, 30}}].
all() ->
- [ei_accept, ei_threaded_accept,
+ [ei_accept,
+ hopeful_random,
+ ei_threaded_accept,
monitor_ei_process].
init_per_testcase(Case, Config) ->
+ rand:uniform(), % Make sure rand is initialized and seeded.
+ %%rand:seed({exsss, [61781477086241372|88832360391433009]}),
+ io:format("** rand seed = ~p\n", [rand:export_seed()]),
runner:init_per_testcase(?MODULE, Case, Config).
ei_accept(Config) when is_list(Config) ->
+
[ei_accept_do(Config, CR, SI)
|| CR <- [0,21],
SI <- [default, ussi]],
@@ -61,11 +75,20 @@ ei_accept_do(Config, CompatRel, SockImpl) ->
%% We take this opportunity to also test export-funs and bit-strings
%% with (ugly) tuple fallbacks in OTP 21 and older.
%% Test both toward pending connection and established connection.
- RealTerms = [<<1:1>>, fun lists:map/2],
+ TermsAndFallbacks =
+ [{<<1:1>>, {<<128>>,1}},
+ {fun lists:map/2, {lists,map}},
+
+ %% Also test funs with hopeful encoding in environment,
+ %% which lead to incorrect fun size encoding (OTP-18104)
+ %% toward pending connection.
+ {fun_with_env(<<1:1>>), fun_with_env({<<128>>,1})},
+ {fun_with_env(fun lists:map/2), fun_with_env({lists,map})}],
+ {RealTerms, Fallbacks} = lists:unzip(TermsAndFallbacks),
EncTerms = case CompatRel of
0 -> RealTerms;
- 21 -> [{<<128>>,1}, {lists,map}]
- end,
+ 21 -> Fallbacks
+ end,
Self = self(),
Funny = fun() -> hello end,
@@ -90,6 +113,226 @@ ei_accept_do(Config, CompatRel, SockImpl) ->
runner:finish(P),
ok.
+fun_with_env(Term) ->
+ Env = ?MODULE:id(Term),
+ fun() -> Env end.
+
+id(X) -> X.
+
+
+%% Send random hopeful encoded terms from emulator to c-node
+%% and verify correct encoding with/without fallback.
+hopeful_random(Config) when is_list(Config) ->
+ [hopeful_random_do(Config, CR, SI)
+ || CR <- [0, 21],
+ SI <- [default, ussi]],
+ ok.
+
+
+hopeful_random_do(Config, CompatRel, SockImpl) ->
+ io:format("CompatRel=~p, SockImpl=~p\n", [CompatRel, SockImpl]),
+ P = runner:start(Config, ?interpret),
+ 0 = ei_connect_init(P, 42, erlang:get_cookie(), 0, CompatRel, SockImpl),
+
+ Myname = hd(tl(string:tokens(atom_to_list(node()), "@"))),
+ io:format("Myname ~p ~n", [Myname]),
+ EINode = list_to_atom("c42@"++Myname),
+ io:format("EINode ~p ~n", [EINode]),
+
+ Port = 6543,
+ {ok, ListenFd} = ei_publish(P, Port),
+
+ Terms = [random_term(20) || _ <- lists:seq(1,10)],
+
+ %% lists:foldl(fun(T,N) ->
+ %% io:format("Term #~p = ~p\n", [N, printable(T)]),
+ %% N+1
+ %% end,
+ %% 1,
+ %% Terms),
+
+ %% Send on pending connection (hopeful encoding)
+ [{any, EINode} ! T || T <- Terms],
+ {ok, Fd, Node} = ei_accept(P, ListenFd),
+ Node = node(),
+ [match(T, ei_receive(P, Fd), CompatRel) || T <- Terms],
+
+ %% Send again on established connection
+ [{any, EINode} ! T || T <- Terms],
+ [match(T, ei_receive(P, Fd), CompatRel) || T <- Terms],
+
+ runner:finish(P),
+ ok.
+
+
+match(A, B, 0) ->
+ match(A, B);
+match(A, B, 21) ->
+ match(fallback(printable(A)),
+ printable(B)). %% B assumed to already be fallback'ed
+
+match(A, A) -> ok;
+match(A, B) ->
+ io:format("match failed\nA = ~p\nB = ~p\n", [A, B]),
+ ct:fail("match failed").
+
+
+%% Convert to fallbacks to bitstrings and export funs.
+%% Does not support local funs with environment terms.
+fallback(Binary) when is_binary(Binary) ->
+ Binary;
+fallback(BitStr) when is_bitstring(BitStr) ->
+ TailBits = bit_size(BitStr) rem 8,
+ PadBits = 8 - TailBits,
+ {<<BitStr/bits, 0:PadBits>>, TailBits};
+fallback(Fun) when is_function(Fun) ->
+ FI = erlang:fun_info(Fun),
+ {type,external} = lists:keyfind(type, 1, FI),
+ {module, Mod} = lists:keyfind(module, 1, FI),
+ {name, Func} = lists:keyfind(name, 1, FI),
+ {Mod, Func};
+fallback([H|T]) ->
+ [fallback(H)|fallback(T)];
+fallback(Tuple) when is_tuple(Tuple) ->
+ list_to_tuple(fallback(tuple_to_list(Tuple)));
+fallback(Map) when is_map(Map) ->
+ maps:from_list(fallback(maps:to_list(Map)));
+fallback(Leaf) ->
+ Leaf.
+
+random_term(MaxSize) ->
+ rand_term(rand:uniform(MaxSize)).
+
+rand_term(Arity) when Arity > 0 ->
+ List = rand_list(Arity, []),
+ case rand:uniform(6) of
+ 1 -> List;
+ 2 -> list_to_improper_list(List);
+ 3 -> list_to_tuple(List);
+ 4 -> list_to_flatmap(List);
+ 5 -> list_to_hashmap(List);
+ 6 -> list_to_fun(List)
+ end;
+rand_term(0) ->
+ rand_leaf().
+
+rand_list(0, Acc) ->
+ %% Shuffle result list to not favor tail heavy lists.
+ {_, MixedList} = lists:unzip(lists:sort(Acc)),
+ MixedList;
+rand_list(Budget, Acc) ->
+ Depth = rand:uniform(Budget),
+ SortIx = rand:uniform(1 bsl 26),
+ rand_list(Budget-Depth, [{SortIx, rand_term(Depth-1)} | Acc]).
+
+rand_leaf() ->
+ case rand:uniform(19) of
+ 1 -> rand_integer();
+ 2 -> rand_float();
+ 3 -> rand_heapbin();
+ 4 -> rand_procbin();
+ 5 -> rand_subbin(rand_heapbin());
+ 6 -> rand_subbin(rand_procbin());
+ 7 -> atom;
+ 8 -> [];
+ 9 -> {};
+ 10 -> #{};
+ 11 -> fun lists:sort/1;
+ 12 -> fun() -> ok end;
+ 13 -> self();
+ 14 -> lists:last(erlang:ports());
+ 15 -> make_ref();
+ 16 -> atomics:new(10,[]); % Magic ref
+ 17 -> mk_ext_pid({a@b, 17}, 17, 42);
+ 18 -> mk_ext_port({a@b, 21}, 13);
+ 19 -> mk_ext_ref({a@b, 42}, [42, 19, 11])
+ end.
+
+rand_integer() ->
+ Bits = rand:uniform(150),
+ Uint = rand:uniform(1 bsl Bits),
+ case rand:uniform(2) of
+ 1 -> Uint;
+ 2 -> -Uint
+ end.
+
+rand_float() ->
+ rand:uniform().
+
+rand_heapbin() ->
+ HeapBinSz = rand:uniform(?ERL_ONHEAP_BIN_LIMIT + 1) - 1,
+ HeapBig = rand:uniform(1 bsl (HeapBinSz*8)),
+ <<HeapBig:HeapBinSz/unit:8>>.
+
+rand_procbin() ->
+ ProcBinSz = ?ERL_ONHEAP_BIN_LIMIT + rand:uniform(?ERL_ONHEAP_BIN_LIMIT),
+ ProcBig = rand:uniform(1 bsl (ProcBinSz*8)),
+ <<ProcBig:ProcBinSz/unit:8>>.
+
+rand_subbin(Bin) ->
+ TotSz = bit_size(Bin),
+ Offs = rand:uniform(TotSz + 1) - 1,
+ Bits = rand:uniform(TotSz - Offs + 1) - 1,
+ <<_:Offs, BitStr:Bits/bits, _/bits>> = Bin,
+ BitStr.
+
+list_to_improper_list([A,B|T]) ->
+ T ++ [A|B];
+list_to_improper_list([H]) ->
+ [[]|H].
+
+list_to_flatmap(List) ->
+ list_to_map(List, #{}).
+
+list_to_hashmap(List) ->
+ HashMap = #{1=>1, 2=>2, 3=>3, 4=>4, 5=>5, 6=>6, 7=>7, 8=>8, 9=>9,10=>0,
+ 11=>1,12=>2,13=>3,14=>4,15=>5,16=>6,17=>7,18=>8,19=>9,20=>0,
+ 21=>1,22=>2,23=>3,24=>4,25=>5,26=>6,27=>7,28=>8,29=>9,30=>0,
+ 31=>1,32=>2,33=>3},
+ list_to_map(List, HashMap).
+
+list_to_map([], Map) ->
+ Map;
+list_to_map([K], Map) ->
+ Map#{K => K};
+list_to_map([K,V|T], Map) ->
+ list_to_map(T, Map#{K => V}).
+
+list_to_fun([X]) ->
+ fun(A) -> A + X end;
+list_to_fun([X, Y]) ->
+ fun(A) -> A + X + Y end;
+list_to_fun([X, Y | T]) ->
+ fun(A) -> [A+X+Y | T] end.
+
+mk_ext_pid({NodeName, Creation}, Number, Serial) ->
+ erts_test_utils:mk_ext_pid({NodeName, Creation}, Number, Serial).
+
+mk_ext_port({NodeName, Creation}, Number) ->
+ erts_test_utils:mk_ext_port({NodeName, Creation}, Number).
+
+mk_ext_ref({NodeName, Creation}, Numbers) ->
+ erts_test_utils:mk_ext_ref({NodeName, Creation}, Numbers).
+
+%% Convert local funs to maps to show fun environment
+printable(Fun) when is_function(Fun) ->
+ case erlang:fun_info(Fun, type) of
+ {type,local} ->
+ {env, Env} = erlang:fun_info(Fun, env),
+ #{'fun' => [printable(T) || T <- Env]};
+ {type,external} ->
+ Fun
+ end;
+printable([H|T]) ->
+ [printable(H)|printable(T)];
+printable(Tuple) when is_tuple(Tuple) ->
+ list_to_tuple(printable(tuple_to_list(Tuple)));
+printable(Map) when is_map(Map) ->
+ maps:from_list(printable(maps:to_list(Map)));
+printable(Leaf) ->
+ Leaf.
+
+
ei_threaded_accept(Config) when is_list(Config) ->
Einode = filename:join(proplists:get_value(data_dir, Config), "eiaccnode"),
ei_threaded_accept_do(Einode, default),
diff --git a/lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_test.c b/lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_test.c
index 7cfc0c9da0..f307646ecc 100644
--- a/lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_test.c
+++ b/lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_test.c
@@ -198,10 +198,13 @@ static void cmd_ei_accept(char* buf, int len)
static void cmd_ei_receive(char* buf, int len)
{
+ static int call_cnt = 0;
ei_x_buff x;
erlang_msg msg;
long l;
int fd, index = 0;
+
+ call_cnt++;
if (ei_decode_long(buf, &index, &l) < 0)
fail("expected int (fd)");
@@ -215,6 +218,22 @@ static void cmd_ei_receive(char* buf, int len)
fail1("ei_xreceive_msg, got==%d", got);
break;
}
+
+ {
+ int index = 0;
+ int skip_ret;
+
+ if (ei_decode_version(x.buff, &index, NULL) != 0)
+ fail("ei_decode_version failed");
+
+ skip_ret = ei_skip_term(x.buff, &index);
+ if (skip_ret != 0)
+ fail1("ei_skip_term returned %d", skip_ret);
+ if (index != x.index )
+ fail3("ei_skip_term length mismatch %d != %d (call_cnt=%d)\n",
+ index, x.index, call_cnt);
+ }
+
index = 1;
send_bin_term(&x);
ei_x_free(&x);
diff --git a/lib/erl_interface/test/runner.erl b/lib/erl_interface/test/runner.erl
index 484890006e..76cbc49907 100644
--- a/lib/erl_interface/test/runner.erl
+++ b/lib/erl_interface/test/runner.erl
@@ -23,7 +23,7 @@
-export([test/2, test/3,
init_per_testcase/3,
- start/2, send_term/2, finish/1, send_eot/1, recv_eot/1,
+ start/2, start/3, send_term/2, finish/1, send_eot/1, recv_eot/1,
get_term/1, get_term/2]).
-define(default_timeout, 5000).
@@ -55,14 +55,21 @@ test(Config, Tc, Timeout) ->
%%
%% Returns: {ok, Port}
-start(Config, {Prog, Tc}) when is_list(Prog), is_integer(Tc) ->
- Port = open_port({spawn, prog_cmd(Config, Prog)},
+start(Config, ProgTc) ->
+ start(Config, ProgTc, []).
+
+start(Config, {Prog, Tc}, Opt) when is_list(Prog), is_integer(Tc) ->
+ Port = open_port({spawn, prog_cmd(Config, Prog, Opt)},
[{packet, 4}, exit_status]),
Command = [Tc div 256, Tc rem 256],
Port ! {self(), {command, Command}},
Port.
-prog_cmd(Config, Prog) ->
+prog_cmd(Config, Prog0, Opt) ->
+ Prog = case Opt of
+ rr -> "rr " ++ Prog0;
+ [] -> Prog0
+ end,
case proplists:get_value(valgrind_cmd_fun, Config) of
undefined ->
Prog;