File 0655-Look-up-IOV_MAX-instead-of-assuming-16.patch of Package erlang
From 76a647835f0e858f896f57702a56d3596eb14d1a Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Wed, 21 Oct 2020 22:37:54 +0200
Subject: [PATCH] Look up IOV_MAX instead of assuming 16
---
erts/emulator/drivers/common/inet_drv.c | 33 +++++++++++++--
erts/emulator/test/distribution_SUITE.erl | 50 ++++++++++++++++++++++-
2 files changed, 78 insertions(+), 5 deletions(-)
diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c
index 567f22199b..00708f1478 100644
--- a/erts/emulator/drivers/common/inet_drv.c
+++ b/erts/emulator/drivers/common/inet_drv.c
@@ -1155,9 +1155,24 @@ typedef struct {
#define TCP_MAX_PACKET_SIZE 0x4000000 /* 64 M */
-#define MAX_VSIZE 16 /* Max number of entries allowed in an I/O
- * vector sock_sendv().
- */
+/* Max number of entries allowed in an I/O vector sock_sendv(). */
+#if defined(__WIN32__)
+/*
+ * Windows 95, 98, and ME is limited to 16, but we do not
+ * support those. Documentation unfortunately does not say
+ * anything about newer windows, so we guess 1024 which
+ * seems to be what most systems use...
+ */
+#define MAX_VSIZE 1024
+#elif !defined(NO_SYSCONF)
+static int iov_max;
+#define MAX_VSIZE iov_max
+#elif defined(IOV_MAX)
+#define MAX_VSIZE IOV_MAX
+#else
+/* POSIX require at least 16 */
+#define MAX_VSIZE 16
+#endif
static int tcp_inet_init(void);
static void tcp_inet_stop(ErlDrvData);
@@ -4127,6 +4142,18 @@ static int inet_init()
if (!sock_init())
goto error;
+#if !defined(__WIN32__) && !defined(NO_SYSCONF)
+ iov_max = (int) sysconf(_SC_IOV_MAX);
+ if (iov_max < 0) {
+#ifdef IOV_MAX
+ iov_max = IOV_MAX;
+#else
+ iov_max = 16; /* min value required by POSIX */
+#endif
+ }
+ ASSERT(iov_max >= 16);
+#endif
+
if (0 != erl_drv_tsd_key_create("inet_buffer_stack_key", &buffer_stack_key))
goto error;
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index 8ec5ceb3ff..d945023f61 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -57,7 +57,8 @@
bad_dist_ext_process_info/1,
bad_dist_ext_control/1,
bad_dist_ext_connection_id/1,
- start_epmd_false/1, epmd_module/1]).
+ start_epmd_false/1, epmd_module/1,
+ huge_iovec/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
@@ -82,7 +83,8 @@ all() ->
dist_parallel_send, atom_roundtrip, unicode_atom_roundtrip, atom_roundtrip_r15b,
contended_atom_cache_entry, contended_unicode_atom_cache_entry,
bad_dist_structure, {group, bad_dist_ext},
- start_epmd_false, epmd_module].
+ start_epmd_false, epmd_module,
+ huge_iovec].
groups() ->
[{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]},
@@ -2023,6 +2025,51 @@ hopefull_export_fun_bug(Config) when is_list(Config) ->
Version = 5,
{port, Port, Version}
end.
+
+huge_iovec(Config) ->
+ %% Make sure that we can pass a term that will produce
+ %% an io-vector larger than IOV_MAX over the distribution...
+ %% IOV_MAX is typically 1024. Currently we produce an
+ %% element in the io-vector for all off heap binaries...
+ NoBinaries = 1 bsl 14,
+ BinarySize = 65,
+ {ok, Node} = start_node(huge_iovec),
+ P = spawn_link(Node,
+ fun () ->
+ receive {From, Data} ->
+ From ! {self(), Data}
+ end
+ end),
+ RBL = mk_rand_bin_list(BinarySize, NoBinaries),
+ %% Check that it actually will produce a huge iovec...
+ %% If we set a limit on the size of the binaries
+ %% that will produce an element in the io-vector
+ %% we need to adjust this testcase...
+ true = length(term_to_iovec(RBL)) >= NoBinaries,
+ P ! {self(), RBL},
+ receive
+ {P, EchoedRBL} ->
+ stop_node(Node),
+ RBL = EchoedRBL
+ end,
+ ok.
+
+mk_rand_bin_list(Bytes, Binaries) ->
+ mk_rand_bin_list(Bytes, Binaries, []).
+
+mk_rand_bin_list(_Bytes, 0, Acc) ->
+ Acc;
+mk_rand_bin_list(Bytes, Binaries, Acc) ->
+ mk_rand_bin_list(Bytes, Binaries-1, [mk_rand_bin(Bytes) | Acc]).
+
+mk_rand_bin(Bytes) ->
+ mk_rand_bin(Bytes, []).
+
+mk_rand_bin(0, Data) ->
+ list_to_binary(Data);
+mk_rand_bin(N, Data) ->
+ mk_rand_bin(N-1, [rand:uniform(256) - 1 | Data]).
+
%%% Utilities
--
2.26.2