File 1331-Testcase-testing-race-between-dirty-and-normal-signa.patch of Package erlang

From 218ab9504edb3a8ee50a1ce503fb4f15fc9e210a Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Tue, 1 Jun 2021 22:58:26 +0200
Subject: [PATCH 1/2] Testcase testing race between dirty and normal signal
 handling

The fix for this issue was implemented in PR-4914. See also GH-4885 and
OTP-17462.

The bug is hard to trigger when it exist. This testcase only
sometimes causes a crash when the bug exist.
---
 erts/emulator/test/signal_SUITE.erl           |  81 ++++++++++-
 .../test/signal_SUITE_data/Makefile.src       |  30 ++++
 .../signal_SUITE_data/unlink_signal_drv.c     | 132 ++++++++++++++++++
 3 files changed, 240 insertions(+), 3 deletions(-)
 create mode 100644 erts/emulator/test/signal_SUITE_data/Makefile.src
 create mode 100644 erts/emulator/test/signal_SUITE_data/unlink_signal_drv.c

diff --git a/erts/emulator/test/signal_SUITE.erl b/erts/emulator/test/signal_SUITE.erl
index 4981d48621..6d726289b6 100644
--- a/erts/emulator/test/signal_SUITE.erl
+++ b/erts/emulator/test/signal_SUITE.erl
@@ -35,7 +35,8 @@
 
 % Test cases
 -export([xm_sig_order/1,
-         kill2killed/1]).
+         kill2killed/1,
+         contended_signal_handling/1]).
 
 init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
     [{testcase, Func}|Config].
@@ -55,8 +56,8 @@ suite() ->
 
 all() -> 
     [xm_sig_order,
-     kill2killed].
-
+     kill2killed,
+     contended_signal_handling].
 
 %% Test that exit signals and messages are received in correct order
 xm_sig_order(Config) when is_list(Config) ->
@@ -152,11 +153,85 @@ spawn_link_line(NodeA, NodeB, Type, N, Tester) ->
                        receive after infinity -> ok end
                end).
 
+contended_signal_handling(Config) when is_list(Config) ->
+    %%
+    %% Test for a race in signal handling of a process.
+    %%
+    %% When executing dirty, a "dirty signal handler"
+    %% process will handle signals for the process. If
+    %% the process stops executing dirty while the dirty
+    %% signal handler process is handling signals on
+    %% behalf of the process, both the dirty signal handler
+    %% process and the process itself might try to handle
+    %% signals for the process at the same time. There used
+    %% to be a bug that caused both processes to enter the
+    %% signal handling code simultaneously when the main
+    %% lock of the process was temporarily released during
+    %% signal handling (see GH-4885/OTP-17462/PR-4914).
+    %% Currently the main lock is only released when the
+    %% process receives an 'unlock' signal from a port,
+    %% and then responds by sending an 'unlock-ack' signal
+    %% to the port. This testcase tries to massage that
+    %% scenario. It is quite hard to cause a crash even
+    %% when the bug exists, but this testcase at least
+    %% sometimes causes a crash when the bug is present.
+    %%
+    process_flag(priority, high),
+    Drv = unlink_signal_drv,
+    ok = load_driver(Config, Drv),
+    try
+        contended_signal_handling_test(Drv, 250)
+    after
+        ok = erl_ddll:unload_driver(Drv)
+    end,
+    ok.
+
+contended_signal_handling_test(_Drv, 0) ->
+    ok;
+contended_signal_handling_test(Drv, N) ->
+    Ports = contended_signal_handling_make_ports(Drv, 100, []),
+    erlang:yield(),
+    contended_signal_handling_cmd_ports(Ports),
+    erts_debug:dirty_cpu(wait, rand:uniform(5)),
+    wait_until(fun () -> Ports == Ports -- erlang:ports() end),
+    contended_signal_handling_test(Drv, N-1).
+
+contended_signal_handling_cmd_ports([]) ->
+    ok;
+contended_signal_handling_cmd_ports([P|Ps]) ->
+    P ! {self(), {command, ""}},
+    contended_signal_handling_cmd_ports(Ps).
+
+contended_signal_handling_make_ports(_Drv, 0, Ports) ->
+    Ports;
+contended_signal_handling_make_ports(Drv, N, Ports) ->
+    Port = open_port({spawn, Drv}, []),
+    true = is_port(Port),
+    contended_signal_handling_make_ports(Drv, N-1, [Port|Ports]).
 
 %%
 %% -- Internal utils --------------------------------------------------------
 %%
 
+load_driver(Config, Driver) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    case erl_ddll:load_driver(DataDir, Driver) of
+        ok ->
+            ok;
+        {error, Error} = Res ->
+            io:format("~s\n", [erl_ddll:format_error(Error)]),
+            Res
+    end.
+
+wait_until(Fun) ->
+    case (catch Fun()) of
+        true ->
+            ok;
+        _ ->
+            receive after 1 -> ok end,
+            wait_until(Fun)
+    end.
+
 repeat(_Fun, N) when is_integer(N), N =< 0 ->
     ok;
 repeat(Fun, N) when is_integer(N)  ->
diff --git a/erts/emulator/test/signal_SUITE_data/Makefile.src b/erts/emulator/test/signal_SUITE_data/Makefile.src
new file mode 100644
index 0000000000..562dc986dc
--- /dev/null
+++ b/erts/emulator/test/signal_SUITE_data/Makefile.src
@@ -0,0 +1,30 @@
+#
+# %CopyrightBegin%
+#
+# Copyright Ericsson AB 2021. All Rights Reserved.
+#
+# Licensed under the Apache License, Version 2.0 (the "License");
+# you may not use this file except in compliance with the License.
+# You may obtain a copy of the License at
+#
+#     http://www.apache.org/licenses/LICENSE-2.0
+#
+# Unless required by applicable law or agreed to in writing, software
+# distributed under the License is distributed on an "AS IS" BASIS,
+# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+# See the License for the specific language governing permissions and
+# limitations under the License.
+#
+# %CopyrightEnd%
+#
+
+CC = @CC@
+LD = @LD@
+CFLAGS = @CFLAGS@ @DEFS@
+CROSSLDFLAGS = @CROSSLDFLAGS@
+
+DRIVERS = unlink_signal_drv@dll@
+
+all: $(DRIVERS)
+
+@SHLIB_RULES@
diff --git a/erts/emulator/test/signal_SUITE_data/unlink_signal_drv.c b/erts/emulator/test/signal_SUITE_data/unlink_signal_drv.c
new file mode 100644
index 0000000000..f441e31182
--- /dev/null
+++ b/erts/emulator/test/signal_SUITE_data/unlink_signal_drv.c
@@ -0,0 +1,132 @@
+/*
+ * %CopyrightBegin%
+ *
+ * Copyright Ericsson AB 2021. All Rights Reserved.
+ *
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ *
+ * %CopyrightEnd%
+ */
+
+#include "erl_driver.h"
+
+static void stop(ErlDrvData drv_data);
+static ErlDrvData start(ErlDrvPort port,
+			char *command);
+static void output(ErlDrvData drv_data,
+		   char *buf, ErlDrvSizeT len);
+static void flush(ErlDrvData drv_data);
+static void timeout(ErlDrvData drv_data);
+static void process_exit(ErlDrvData drv_data, ErlDrvMonitor *monitor);
+
+static ErlDrvEntry unlink_signal_entry = { 
+    NULL /* init */,
+    start,
+    stop,
+    output,
+    NULL /* ready_input */,
+    NULL /* ready_output */,
+    "unlink_signal_drv",
+    NULL /* finish */,
+    NULL /* handle */,
+    NULL /* control */,
+    timeout,
+    NULL /* outputv */,
+    NULL /* ready_async */,
+    flush,
+    NULL /* call */,
+    NULL /* event */,
+    ERL_DRV_EXTENDED_MARKER,
+    ERL_DRV_EXTENDED_MAJOR_VERSION,
+    ERL_DRV_EXTENDED_MINOR_VERSION,
+    ERL_DRV_FLAG_USE_PORT_LOCKING,
+    NULL /* handle2 */,
+    process_exit,
+    NULL /* stop_select */
+};
+
+DRIVER_INIT(unlink_signal_entry)
+{
+    return &unlink_signal_entry;
+}
+
+typedef struct {
+    ErlDrvData port;
+    int timeout_count;
+} us_drv_state;
+
+static void stop(ErlDrvData drv_data)
+{
+    driver_free((void *) drv_data);
+}
+
+static ErlDrvData start(ErlDrvPort port,
+			char *command)
+{
+    us_drv_state *state = (us_drv_state *) driver_alloc(sizeof(us_drv_state));
+    state->port = port;
+    state->timeout_count = 0;
+    return (ErlDrvData) state;
+}
+
+static void output(ErlDrvData drv_data,
+		   char *buf, ErlDrvSizeT len)
+{
+    us_drv_state *state = (us_drv_state *) drv_data;
+    driver_set_timer(state->port, 2);
+}
+
+static void flush(ErlDrvData drv_data)
+{
+    us_drv_state *state = (us_drv_state *) drv_data;
+    driver_set_timer(state->port, 5);
+}
+
+static void timeout(ErlDrvData drv_data)
+{
+    us_drv_state *state = (us_drv_state *) drv_data;
+    state->timeout_count++;
+    if (state->timeout_count == 1) {
+        int i, limit;
+        ErlDrvTermData connected = driver_connected(state->port);
+        /*
+         * Prevent completion of port termination, so that connected
+         * process will be able to send an unlink-ack signal to the
+         * port...
+         */
+        driver_enq(state->port, "x", 1);
+        limit = (int) (((unsigned)state->port) % 1000);
+        /*
+         * Spam connected process with various amounts of monitor,
+         * demonitor signals...
+         */
+        for (i = 0; i < limit; i++) {
+            ErlDrvMonitor *monitor = driver_alloc(sizeof(ErlDrvMonitor));
+            driver_monitor_process(state->port, connected, monitor);
+            driver_demonitor_process(state->port, monitor);
+            driver_free(monitor);
+        }
+        /* driver_exit() will send an unlink signal to conneced process... */
+        driver_exit(state->port, 0);
+    }
+    else {
+        /* Let port complete termination.. */
+        driver_deq(state->port, 1);
+    }
+}
+
+static void
+process_exit(ErlDrvData drv_data, ErlDrvMonitor *monitor)
+{
+    driver_free(monitor);
+}
-- 
2.26.2

openSUSE Build Service is sponsored by