File 3573-erts-Optionally-include-off-heap-binaries-into-max_h.patch of Package erlang

From 7a90b4c68badbfdd7d5a9f7550603621dab07292 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Thu, 22 Sep 2022 15:26:31 +0200
Subject: [PATCH 3/3] erts: Optionally include off-heap binaries into
 max_heap_size

---
 erts/doc/src/erl_cmd.xml             |   8 ++
 erts/doc/src/erlang.xml              |  26 ++++++-
 erts/emulator/beam/atom.names        |   1 +
 erts/emulator/beam/erl_gc.c          |  29 ++++++-
 erts/emulator/beam/erl_gc.h          |   2 +-
 erts/emulator/beam/erl_init.c        |  14 ++++
 erts/emulator/beam/erl_process.h     |   9 ++-
 erts/emulator/test/process_SUITE.erl | 111 ++++++++++++++++++---------
 erts/etc/common/erlexec.c            |   1 +
 erts/preloaded/src/erlang.erl        |   3 +-
 10 files changed, 156 insertions(+), 48 deletions(-)

diff --git a/erts/doc/src/erl_cmd.xml b/erts/doc/src/erl_cmd.xml
index 9069061ae4..d3b00f83d8 100644
--- a/erts/doc/src/erl_cmd.xml
+++ b/erts/doc/src/erl_cmd.xml
@@ -949,6 +949,14 @@ $ <input>erl \
           <seeerl marker="erlang#process_flag_max_heap_size">
           <c>process_flag(max_heap_size, MaxHeapSize)</c></seeerl>.</p>
       </item>
+      <tag><marker id="+hmaxib"/><c><![CDATA[+hmaxib true|false]]></c></tag>
+      <item>
+        <p>Sets whether to include the size of shared off-heap binaries
+          in the sum compared against the maximum heap size. Defaults to
+	  <c>false</c>. For more information, see
+          <seeerl marker="erlang#process_flag_max_heap_size">
+          <c>process_flag(max_heap_size, MaxHeapSize)</c></seeerl>.</p>
+      </item>
       <tag><marker id="+hmaxk"/><c><![CDATA[+hmaxk true|false]]></c></tag>
       <item>
         <p>Sets whether to kill processes reaching the maximum heap size or not.
diff --git a/erts/doc/src/erlang.xml b/erts/doc/src/erlang.xml
index d409905ba3..e25976c38b 100644
--- a/erts/doc/src/erlang.xml
+++ b/erts/doc/src/erlang.xml
@@ -6468,6 +6468,26 @@ receive_replies(ReqId, N, Acc) ->
               or <seeerl marker="#system_flag_max_heap_size">
               <c>erlang:system_flag(max_heap_size, MaxHeapSize)</c></seeerl>.</p>
           </item>
+          <tag><c>include_shared_binaries</c></tag>
+          <item>
+            <p>
+	      When set to <c>true</c>, off-heap binaries are included in the
+	      total sum compared against the <c>size</c> limit. Off-heap binaries
+	      are typically larger binaries that may be shared between
+	      processes. The size of a shared binary is included by all
+	      processes that are referring it. Also, the entire size of a large
+	      binary may be included even if only a smaller part of it is
+	      referred by the process.
+            </p>
+	    <p>
+	      If <c>include_shared_binaries</c> is not defined in the map, the
+	      system default is used. The default system default is <c>false</c>.
+              It can be changed by either the option
+              <seecom marker="erl#+hmaxib">+hmaxib</seecom> in <c>erl(1)</c>,
+              or <seeerl marker="#system_flag_max_heap_size">
+              <c>erlang:system_flag(max_heap_size, MaxHeapSize)</c></seeerl>.
+            </p>
+          </item>
         </taglist>
         <p>The heap size of a process is quite hard to predict, especially the
           amount of memory that is used during the garbage collection. When
@@ -10415,8 +10435,10 @@ Metadata = #{ pid => pid(),
               system-wide maximum heap size settings for spawned processes.
               This setting can be set using the command-line flags
               <seecom marker="erl#+hmax"><c>+hmax</c></seecom>,
-              <seecom marker="erl#+hmaxk"><c>+hmaxk</c></seecom> and
-              <seecom marker="erl#+hmaxel"><c>+hmaxel</c></seecom> in
+              <seecom marker="erl#+hmaxk"><c>+hmaxk</c></seecom>,
+              <seecom marker="erl#+hmaxel"><c>+hmaxel</c></seecom> and
+	      <seecom marker="erl#+hmaxib"><c>+hmaxibl</c></seecom> in
+
               <c>erl(1)</c>. It can also be changed at runtime using
               <seeerl marker="#system_flag_max_heap_size">
               <c>erlang:system_flag(max_heap_size, MaxHeapSize)</c></seeerl>.
diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names
index 274a8e23d4..40a37fb288 100644
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -363,6 +363,7 @@ atom ignore
 atom in
 atom in_exiting
 atom inactive
+atom include_shared_binaries
 atom incomplete
 atom inconsistent
 atom index
diff --git a/erts/emulator/beam/erl_gc.c b/erts/emulator/beam/erl_gc.c
index 2e2a028fc8..fc8065d05c 100644
--- a/erts/emulator/beam/erl_gc.c
+++ b/erts/emulator/beam/erl_gc.c
@@ -158,6 +158,7 @@ static void offset_rootset(Process *p, Sint heap_offs, Sint stack_offs,
                            char* area, Uint area_sz, Eterm* objv, int nobj);
 static void offset_off_heap(Process* p, Sint offs, char* area, Uint area_sz);
 static void offset_mqueue(Process *p, Sint offs, char* area, Uint area_sz);
+static int has_reached_max_heap_size(Process *p, Uint total_heap_size);
 static int reached_max_heap_size(Process *p, Uint total_heap_size,
                                  Uint extra_heap_size, Uint extra_old_heap_size);
 static void init_gc_info(ErtsGCInfo *gcip);
@@ -1155,7 +1156,7 @@ erts_garbage_collect_literals(Process* p, Eterm* literals,
         new_heap_size = HEAP_END(p) - HEAP_START(p);
         old_heap_size = erts_next_heap_size(lit_size, 0);
         total_heap_size = new_heap_size + old_heap_size;
-        if (MAX_HEAP_SIZE_GET(p) < total_heap_size &&
+        if (has_reached_max_heap_size(p, total_heap_size) &&
             reached_max_heap_size(p, total_heap_size,
                                   new_heap_size, old_heap_size)) {
             erts_set_self_exiting(p, am_killed);
@@ -1387,7 +1388,7 @@ minor_collection(Process* p, ErlHeapFragment *live_hf_end,
         extra_heap_size = next_heap_size(p, stack_size + MAX(size_before,need), 0);
         heap_size += extra_heap_size;
 
-        if (heap_size > MAX_HEAP_SIZE_GET(p))
+        if (has_reached_max_heap_size(p, heap_size))
             if (reached_max_heap_size(p, heap_size, extra_heap_size, extra_old_heap_size))
                 return -2;
     }
@@ -1836,7 +1837,7 @@ major_collection(Process* p, ErlHeapFragment *live_hf_end,
         /* Add size of new young heap */
         heap_size += new_sz;
 
-        if (MAX_HEAP_SIZE_GET(p) < heap_size)
+        if (has_reached_max_heap_size(p, heap_size))
             if (reached_max_heap_size(p, heap_size, new_sz, 0))
                 return -2;
     }
@@ -3679,6 +3680,16 @@ erts_process_gc_info(Process *p, Uint *sizep, Eterm **hpp,
     return res;
 }
 
+static int has_reached_max_heap_size(Process *p, Uint total_heap_size)
+{
+    Uint used = total_heap_size;
+
+    if (MAX_HEAP_SIZE_FLAGS_GET(p) & MAX_HEAP_SIZE_INCLUDE_OH_BINS) {
+        used += p->bin_old_vheap + p->off_heap.overhead;
+    }
+    return (used > MAX_HEAP_SIZE_GET(p));
+}
+
 static int
 reached_max_heap_size(Process *p, Uint total_heap_size,
                       Uint extra_heap_size, Uint extra_old_heap_size)
@@ -3743,10 +3754,11 @@ erts_max_heap_size_map(ErtsHeapFactory *factory,
                        Sint max_heap_size, Uint max_heap_flags)
 {
     Eterm keys[] = {
-        am_error_logger, am_kill, am_size
+        am_error_logger, am_include_shared_binaries, am_kill, am_size
     };
     Eterm values[] = {
         max_heap_flags & MAX_HEAP_SIZE_LOG ? am_true : am_false,
+        max_heap_flags & MAX_HEAP_SIZE_INCLUDE_OH_BINS ? am_true : am_false,
         max_heap_flags & MAX_HEAP_SIZE_KILL ? am_true : am_false,
         make_small(max_heap_size)
     };
@@ -3767,6 +3779,7 @@ erts_max_heap_size(Eterm arg, Uint *max_heap_size, Uint *max_heap_flags)
         const Eterm *size = erts_maps_get(am_size, arg);
         const Eterm *kill = erts_maps_get(am_kill, arg);
         const Eterm *log = erts_maps_get(am_error_logger, arg);
+        const Eterm *incl_bins = erts_maps_get(am_include_shared_binaries, arg);
         if (size && is_small(*size)) {
             sz = signed_val(*size);
         } else {
@@ -3789,6 +3802,14 @@ erts_max_heap_size(Eterm arg, Uint *max_heap_size, Uint *max_heap_flags)
             else
                 return 0;
         }
+        if (incl_bins) {
+            if (*incl_bins == am_true)
+                *max_heap_flags |= MAX_HEAP_SIZE_INCLUDE_OH_BINS;
+            else if (*incl_bins == am_false)
+                *max_heap_flags &= ~MAX_HEAP_SIZE_INCLUDE_OH_BINS;
+            else
+                return 0;
+        }
     } else
         return 0;
     if (sz < 0)
diff --git a/erts/emulator/beam/erl_gc.h b/erts/emulator/beam/erl_gc.h
index 262c040974..c1760562c9 100644
--- a/erts/emulator/beam/erl_gc.h
+++ b/erts/emulator/beam/erl_gc.h
@@ -160,7 +160,7 @@ typedef struct {
   Uint64 garbage_cols;
 } ErtsGCInfo;
 
-#define ERTS_MAX_HEAP_SIZE_MAP_SZ (2*3 + 1 + MAP_HEADER_FLATMAP_SZ)
+#define ERTS_MAX_HEAP_SIZE_MAP_SZ (2*4 + 1 + MAP_HEADER_FLATMAP_SZ)
 
 #define ERTS_PROCESS_GC_INFO_MAX_TERMS (11)  /* number of elements in process_gc_info*/
 #define ERTS_PROCESS_GC_INFO_MAX_SIZE                                   \
diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c
index 577657bbb2..1de7403894 100644
--- a/erts/emulator/beam/erl_init.c
+++ b/erts/emulator/beam/erl_init.c
@@ -631,6 +631,7 @@ void erts_usage(void)
 	       H_DEFAULT_MAX_SIZE);
     erts_fprintf(stderr, "-hmaxk bool    enable or disable kill at max heap size (default true)\n");
     erts_fprintf(stderr, "-hmaxel bool   enable or disable error_logger report at max heap size (default true)\n");
+    erts_fprintf(stderr, "-hmaxib bool   enable or disable including off-heap binaries into max heap size (default false)\n");
     erts_fprintf(stderr, "-hpds size     set initial process dictionary size (default %d)\n",
 	       erts_pd_initial_size);
     erts_fprintf(stderr, "-hmqd  val     set default message queue data flag for processes;\n");
@@ -1580,6 +1581,8 @@ erl_start(int argc, char **argv)
              * h|max   - max_heap_size
              * h|maxk  - max_heap_kill
              * h|maxel - max_heap_error_logger
+             * h|maxib - map_heap_include_shared_binaries
+             *
 	     *
 	     */
 	    if (has_prefix("mbs", sub_param)) {
@@ -1642,6 +1645,17 @@ erl_start(int argc, char **argv)
 		    erts_usage();
 		}
 		VERBOSE(DEBUG_SYSTEM, ("using max heap log %d\n", H_MAX_FLAGS));
+            } else if (has_prefix("maxib", sub_param)) {
+                arg = get_arg(sub_param+5, argv[i+1], &i);
+                if (sys_strcmp(arg,"true") == 0) {
+                    H_MAX_FLAGS |= MAX_HEAP_SIZE_INCLUDE_OH_BINS;
+                } else if (sys_strcmp(arg,"false") == 0) {
+                    H_MAX_FLAGS &= ~MAX_HEAP_SIZE_INCLUDE_OH_BINS;
+                } else {
+                    erts_fprintf(stderr, "bad max heap include bins %s\n", arg);
+                    erts_usage();
+                }
+                VERBOSE(DEBUG_SYSTEM, ("using max heap log %d\n", H_MAX_FLAGS));
 	    } else if (has_prefix("max", sub_param)) {
                 Sint hMaxSize;
                 char *rest;
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index 36b483acf4..dbc94d8d66 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -993,14 +993,15 @@ typedef struct ErtsProcSysTaskQs_ ErtsProcSysTaskQs;
 #  define MSO(p)            (p)->off_heap
 #  define MIN_HEAP_SIZE(p)  (p)->min_heap_size
 
-#  define MAX_HEAP_SIZE_GET(p)     ((p)->max_heap_size >> 2)
-#  define MAX_HEAP_SIZE_SET(p, sz) ((p)->max_heap_size = ((sz) << 2) |  \
+#  define MAX_HEAP_SIZE_GET(p)     ((p)->max_heap_size >> 3)
+#  define MAX_HEAP_SIZE_SET(p, sz) ((p)->max_heap_size = ((sz) << 3) |  \
                                     MAX_HEAP_SIZE_FLAGS_GET(p))
-#  define MAX_HEAP_SIZE_FLAGS_GET(p)          ((p)->max_heap_size & 0x3)
+#  define MAX_HEAP_SIZE_FLAGS_GET(p)          ((p)->max_heap_size & 0x7)
 #  define MAX_HEAP_SIZE_FLAGS_SET(p, flags)   ((p)->max_heap_size = flags | \
-                                               ((p)->max_heap_size & ~0x3))
+                                               ((p)->max_heap_size & ~0x7))
 #  define MAX_HEAP_SIZE_KILL 1
 #  define MAX_HEAP_SIZE_LOG  2
+#  define MAX_HEAP_SIZE_INCLUDE_OH_BINS 4
 
 struct process {
     ErtsPTabElementCommon common; /* *Need* to be first in struct */
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 73e0b04100..bd9fa32fbf 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -222,6 +222,7 @@ end_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
     erlang:system_flag(max_heap_size,
                        #{size => 0,
                          kill => true,
+                         include_shared_binaries => false,
                          error_logger => true}),
     erts_test_utils:ept_check_leaked_nodes(Config).
 
@@ -527,7 +528,8 @@ t_process_info(Config) when is_list(Config) ->
     {status, running} = process_info(self(), status),
     {min_heap_size, 233} = process_info(self(), min_heap_size),
     {min_bin_vheap_size,46422} = process_info(self(), min_bin_vheap_size),
-    {max_heap_size, #{ size := 0, kill := true, error_logger := true}} =
+    {max_heap_size, #{ size := 0, kill := true, error_logger := true,
+                       include_shared_binaries := false}} =
         process_info(self(), max_heap_size),
     {current_function,{?MODULE,t_process_info,1}} =
 	process_info(self(), current_function),
@@ -685,8 +687,9 @@ process_info_other_msg(Config) when is_list(Config) ->
 
     {min_heap_size, 233} = process_info(Pid, min_heap_size),
     {min_bin_vheap_size, 46422} = process_info(Pid, min_bin_vheap_size),
-    {max_heap_size, #{ size := 0, kill := true, error_logger := true}} =
-        process_info(self(), max_heap_size),
+    {max_heap_size, #{ size := 0, kill := true, error_logger := true,
+                       include_shared_binaries := false}} =
+        process_info(Pid, max_heap_size),
 
     Pid ! stop,
     ok.
@@ -1943,6 +1946,8 @@ process_flag_badarg(Config) when is_list(Config) ->
                                                         kill => gurka }) end),
     chk_badarg(fun () -> process_flag(max_heap_size, #{ size => 233,
                                                         error_logger => gurka }) end),
+    chk_badarg(fun () -> process_flag(max_heap_size, #{ size => 233,
+                                                        include_shared_binaries => gurka}) end),
     chk_badarg(fun () -> process_flag(max_heap_size, #{ size => 233,
                                                         kill => true,
                                                         error_logger => gurka }) end),
@@ -2593,63 +2598,72 @@ spawn_opt_max_heap_size(_Config) ->
             flush()
     end,
 
+    spawn_opt_max_heap_size_do(fun oom_fun/1),
+
+    io:format("Repeat tests with refc binaries\n",[]),
+
+    spawn_opt_max_heap_size_do(fun oom_bin_fun/1),
+
+    error_logger:delete_report_handler(?MODULE),
+    ok.
+
+spawn_opt_max_heap_size_do(OomFun) ->
+    Max = 2024,
     %% Test that numerical limit works
-    max_heap_size_test(1024, 1024, true, true),
+    max_heap_size_test(Max, Max, true, true, OomFun),
 
     %% Test that map limit works
-    max_heap_size_test(#{ size => 1024 }, 1024, true, true),
+    max_heap_size_test(#{ size => Max }, Max, true, true, OomFun),
 
     %% Test that no kill is sent
-    max_heap_size_test(#{ size => 1024, kill => false }, 1024, false, true),
+    max_heap_size_test(#{ size => Max, kill => false }, Max, false, true, OomFun),
 
     %% Test that no error_logger report is sent
-    max_heap_size_test(#{ size => 1024, error_logger => false }, 1024, true, false),
+    max_heap_size_test(#{ size => Max, error_logger => false }, Max, true, false, OomFun),
 
     %% Test that system_flag works
-    erlang:system_flag(max_heap_size, #{ size => 0, kill => false,
-                                         error_logger => true}),
-    max_heap_size_test(#{ size => 1024 }, 1024, false, true),
-    max_heap_size_test(#{ size => 1024, kill => true }, 1024, true, true),
+    erlang:system_flag(max_heap_size, OomFun(#{ size => 0, kill => false,
+                                                error_logger => true})),
+    max_heap_size_test(#{ size => Max }, Max, false, true, OomFun),
+    max_heap_size_test(#{ size => Max, kill => true }, Max, true, true, OomFun),
 
-    erlang:system_flag(max_heap_size, #{ size => 0, kill => true,
-                                         error_logger => false}),
-    max_heap_size_test(#{ size => 1024 }, 1024, true, false),
-    max_heap_size_test(#{ size => 1024, error_logger => true }, 1024, true, true),
+    erlang:system_flag(max_heap_size, OomFun(#{ size => 0, kill => true,
+                                                error_logger => false})),
+    max_heap_size_test(#{ size => Max }, Max, true, false, OomFun),
+    max_heap_size_test(#{ size => Max, error_logger => true }, Max, true, true, OomFun),
 
-    erlang:system_flag(max_heap_size, #{ size => 1 bsl 20, kill => true,
-                                         error_logger => true}),
-    max_heap_size_test(#{ }, 1 bsl 20, true, true),
+    erlang:system_flag(max_heap_size, OomFun(#{ size => 1 bsl 16, kill => true,
+                                                error_logger => true})),
+    max_heap_size_test(#{ }, 1 bsl 16, true, true, OomFun),
 
     erlang:system_flag(max_heap_size, #{ size => 0, kill => true,
                                          error_logger => true}),
 
     %% Test that ordinary case works as expected again
-    max_heap_size_test(1024, 1024, true, true),
+    max_heap_size_test(Max, Max, true, true, OomFun),
+    ok.
 
-    error_logger:delete_report_handler(?MODULE),
 
-    ok.
+mhs_spawn_opt(Option) when map_get(size, Option) > 0;
+                           is_integer(Option) ->
+    [{max_heap_size, Option}];
+mhs_spawn_opt(_) ->
+    [].
 
-max_heap_size_test(Option, Size, Kill, ErrorLogger)
-  when map_size(Option) == 0 ->
-    max_heap_size_test([], Size, Kill, ErrorLogger);
-max_heap_size_test(Option, Size, Kill, ErrorLogger)
-  when is_map(Option); is_integer(Option) ->
-    max_heap_size_test([{max_heap_size, Option}], Size, Kill, ErrorLogger);
-max_heap_size_test(Option, Size, Kill, ErrorLogger) ->
-    OomFun = fun () -> oom_fun([]) end,
-    Pid = spawn_opt(OomFun, Option),
+max_heap_size_test(Option, Size, Kill, ErrorLogger, OomFun) ->
+    SpOpt = mhs_spawn_opt(OomFun(Option)),
+    Pid = spawn_opt(fun()-> OomFun(run) end, SpOpt),
     {max_heap_size, MHSz} = erlang:process_info(Pid, max_heap_size),
-    ct:log("Default: ~p~nOption: ~p~nProc: ~p~n",
-           [erlang:system_info(max_heap_size), Option, MHSz]),
+    ct:log("Default: ~p~nOption: ~p~nProc: ~p~nSize = ~p~nSpOpt = ~p~n",
+           [erlang:system_info(max_heap_size), Option, MHSz, Size, SpOpt]),
 
     #{ size := Size} = MHSz,
 
     Ref = erlang:monitor(process, Pid),
     if Kill ->
             receive
-                {'DOWN', Ref, process, Pid, killed} ->
-                    ok
+                {'DOWN', Ref, process, Pid, Reason} ->
+                    killed = Reason
             end;
        true ->
             ok
@@ -2680,12 +2694,37 @@ max_heap_size_test(Option, Size, Kill, ErrorLogger) ->
     %% Make sure that there are no unexpected messages.
     receive_unexpected().
 
-oom_fun(Acc0) ->
+oom_fun(Max) when is_integer(Max) -> Max;
+oom_fun(Map) when is_map(Map)-> Map;
+oom_fun(run) ->
+    io:format("oom_fun() started\n",[]),
+    oom_run_fun([], 100).
+
+oom_run_fun(Acc0, 0) ->
+    done;
+oom_run_fun(Acc0, N) ->
     %% This is tail-recursive since the compiler is smart enough to figure
     %% out that a body-recursive variant never returns, and loops forever
     %% without keeping the list alive.
     timer:sleep(5),
-    oom_fun([lists:seq(1, 1000) | Acc0]).
+    oom_run_fun([lists:seq(1, 1000) | Acc0], N-1).
+
+oom_bin_fun(Max) when is_integer(Max) -> oom_bin_fun(#{size => Max});
+oom_bin_fun(Map) when is_map(Map) -> Map#{include_shared_binaries => true};
+oom_bin_fun(run) ->
+    oom_bin_run_fun([], 10).
+
+oom_bin_run_fun(Acc0, 0) ->
+    done;
+oom_bin_run_fun(Acc0, N) ->
+    timer:sleep(5),
+    oom_bin_run_fun([build_refc_bin(160, <<>>) | Acc0], N-1).
+
+build_refc_bin(0, Acc) ->
+    Acc;
+build_refc_bin(N, Acc) ->
+    build_refc_bin(N-1, <<Acc/binary, 0:(1000*8)>>).
+
 
 receive_error_messages(Pid) ->
     receive
diff --git a/erts/etc/common/erlexec.c b/erts/etc/common/erlexec.c
index c9a662e70f..888df87e35 100644
--- a/erts/etc/common/erlexec.c
+++ b/erts/etc/common/erlexec.c
@@ -152,6 +152,7 @@ static char *plush_val_switches[] = {
     "max",
     "maxk",
     "maxel",
+    "maxib",
     "mqd",
     "",
     NULL
diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl
index 6ac524528d..71a50ddcde 100644
--- a/erts/preloaded/src/erlang.erl
+++ b/erts/preloaded/src/erlang.erl
@@ -3093,7 +3093,8 @@ spawn_monitor(M, F, A) ->
         %% TODO change size => to := when -type maps support is finalized
       | #{ size => non_neg_integer(),
            kill => boolean(),
-           error_logger => boolean() }.
+           error_logger => boolean(),
+           include_shared_binaries => boolean() }.
 
 -type spawn_opt_option() ::
 	link
-- 
2.35.3

openSUSE Build Service is sponsored by