File 1221-Fix-busy-port-handling-in-port_command.patch of Package erlang

From cd4d45fbdd8b6f3e0085d3d61f2dd5f7805f7d82 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Thu, 27 May 2021 15:33:43 +0200
Subject: [PATCH] Fix busy port handling in port_command()

---
 erts/emulator/beam/erl_bif_port.c      |  4 +--
 erts/emulator/test/busy_port_SUITE.erl | 47 +++++++++++++++++++++++---
 2 files changed, 44 insertions(+), 7 deletions(-)

diff --git a/erts/emulator/beam/erl_bif_port.c b/erts/emulator/beam/erl_bif_port.c
index 40a2fb96d6..5f1efcba6c 100644
--- a/erts/emulator/beam/erl_bif_port.c
+++ b/erts/emulator/beam/erl_bif_port.c
@@ -206,8 +206,8 @@ BIF_RETTYPE erts_internal_port_command_3(BIF_ALIST_3)
 	    ERTS_BIF_PREP_RET(res, am_false);
 	else {
 	    erts_suspend(BIF_P, ERTS_PROC_LOCK_MAIN, prt);
-	    ERTS_BIF_PREP_YIELD3(res, bif_export[BIF_erts_internal_port_command_3],
-				 BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3);
+	    ERTS_BIF_YIELD3(bif_export[BIF_erts_internal_port_command_3],
+			    BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3);
 	}
 	break;
     case ERTS_PORT_OP_BUSY_SCHEDULED:
diff --git a/erts/emulator/test/busy_port_SUITE.erl b/erts/emulator/test/busy_port_SUITE.erl
index 4e7004a424..6f80885641 100644
--- a/erts/emulator/test/busy_port_SUITE.erl
+++ b/erts/emulator/test/busy_port_SUITE.erl
@@ -42,7 +42,7 @@ all() ->
      no_trap_exit, no_trap_exit_unlinked, trap_exit,
      multiple_writers, hard_busy_driver, soft_busy_driver,
      scheduling_delay_busy,scheduling_delay_busy_nosuspend,
-     scheduling_busy_link].
+     scheduling_busy_link, busy_with_signals].
 
 end_per_testcase(_Case, Config) when is_list(Config) ->
     case whereis(busy_drv_server) of
@@ -769,13 +769,49 @@ replace_args(Tuple,Vars) when is_tuple(Tuple) ->
 replace_args(Else,_Vars) ->
     Else.
 
+busy_with_signals(Config) when is_list(Config) ->
+    ct:timetrap({seconds, 30}),
+
+    start_busy_driver(Config),
+    {_Owner, Port} = get_slave(),
+    Self = self(),
+
+    process_flag(scheduler, 1),
+    process_flag(priority, high),
+
+    {Pid, Mon} = spawn_opt(fun () ->
+                                   process_flag(trap_exit, true),
+                                   Self ! prepared,
+                                   receive go -> ok end,
+                                   port_command(Port, "plong")
+                           end,
+                           [monitor,
+                            {scheduler, 1},
+                            {priority, normal}]),
+    receive prepared -> ok end,
+    ok = command(lock),
+    Pid ! go,
+    flood_with_exit_signals(Pid, 1000000),
+    ok = command(unlock),
+    receive
+        {'DOWN', Mon, process, Pid, Reason} ->
+            normal = Reason
+    end,
+    ok = command(stop),
+    ok.
+
+flood_with_exit_signals(_Pid, 0) ->
+    ok;
+flood_with_exit_signals(Pid, N) ->
+    exit(Pid, pling),
+    flood_with_exit_signals(Pid, N-1).
+
+%%% Utilities.
+
 pal(_F,_A) -> ok.
 %pal(Format,Args) ->
 %    ct:pal("~p "++Format,[self()|Args]).
 %    erlang:display(lists:flatten(io_lib:format("~p "++Format,[self()|Args]))).
-			
-
-%%% Utilities.
 
 chk_range(Min, Val, Max) when Min =< Val, Val =< Max ->
     ok;
-- 
2.26.2

openSUSE Build Service is sponsored by