File 1424-Fix-race-between-exiting-port-and-signal-handling.patch of Package erlang

From a6f8be76ed92e84334812712647df326022dba94 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Tue, 21 Sep 2021 17:47:46 +0200
Subject: [PATCH] Fix race between exiting port and signal handling

A race between an exiting port and handling of simultaneously
received signals to that port could cause a runtime system crash
due to double free of memory. The effected signals are link,
monitor and demonitor. A similiar race could also cause a memory
leak when receiving an unlink signal.
---
 erts/emulator/beam/io.c                       |  34 +-
 erts/emulator/test/port_SUITE.erl             | 363 +++++++++++++++++-
 erts/emulator/test/port_SUITE_data/echo_drv.c |  22 +-
 3 files changed, 394 insertions(+), 25 deletions(-)

diff --git a/erts/emulator/beam/io.c b/erts/emulator/beam/io.c
index 5f81449eab..c7192fd3df 100644
--- a/erts/emulator/beam/io.c
+++ b/erts/emulator/beam/io.c
@@ -1166,7 +1166,6 @@ erts_schedule_proc2port_signal(Process *c_p,
 			       ErtsPortTaskHandle *pthp,
 			       ErtsProc2PortSigCallback callback)
 {
-    int sched_res;
     if (!refp) {
 	if (c_p)
 	    erts_proc_unlock(c_p, ERTS_PROC_LOCK_MAIN);
@@ -1199,28 +1198,23 @@ erts_schedule_proc2port_signal(Process *c_p,
 
     sigdp->caller = caller;
 
-    /* Schedule port close call for later execution... */
-    sched_res = erts_port_task_schedule(prt->common.id,
-					pthp,
-					ERTS_PORT_TASK_PROC_SIG,
-					sigdp,
-					callback,
-					task_flags);
+    /*
+     * Schedule port execution of the callback. Note that
+     * the callback will be called even if we aren't
+     * able to lookup the port or if its state is invalid.
+     * Callback will in that case be called in "abort mode".
+     * We therefore always return ERTS_PORT_OP_SCHEDULED.
+     */
+    (void) erts_port_task_schedule(prt->common.id,
+                                   pthp,
+                                   ERTS_PORT_TASK_PROC_SIG,
+                                   sigdp,
+                                   callback,
+                                   task_flags);
 
     if (c_p)
 	erts_proc_lock(c_p, ERTS_PROC_LOCK_MAIN);
 
-    /*
-     * Only report dropped if the operation fails to schedule
-     * and no message reference has been passed along. If
-     * message reference has been passed along, a message
-     * reply will be sent regardless of successful schedule
-     * or not, i.e. report scheduled. Abortion of port task
-     * will send message in case of failure.
-     */
-    if (sched_res != 0 && !refp)
-        return ERTS_PORT_OP_DROPPED;
-    
     return ERTS_PORT_OP_SCHEDULED;
 }
 
diff --git a/erts/emulator/test/port_SUITE.erl b/erts/emulator/test/port_SUITE.erl
index eb9b94a316..a2cc05f59d 100644
--- a/erts/emulator/test/port_SUITE.erl
+++ b/erts/emulator/test/port_SUITE.erl
@@ -140,6 +140,21 @@
     win_massive_client/1
 ]).
 
+-export([port_exit_monitor_race/1,
+         port_exit_demonitor_race/1,
+         port_exit_link_race/1,
+         port_exit_unlink_race/1,
+         port_exit_command_race/1,
+         port_exit_connect_race/1,
+         port_exit_close_race/1,
+         port_exit_exit_race/1,
+         port_exit_command_request_race/1,
+         port_exit_connect_request_race/1,
+         port_exit_close_request_race/1,
+         port_exit_control_request_race/1,
+         port_exit_call_request_race/1,
+         port_exit_info_request_race/1]).
+
 -export([do_iter_max_ports/2, relative_cd/0]).
 
 %% Internal exports.
@@ -179,14 +194,28 @@ all() ->
      mon_port_bad_named,
      mon_port_pid_demonitor,
      mon_port_name_demonitor,
-     mon_port_driver_die
-    ].
+     mon_port_driver_die,
+     {group, port_exit_signal_race}].
 
 groups() ->
     [{stream, [], [stream_small, stream_big]},
      {options, [], [t_binary, eof, input_only, output_only]},
      {multiple_packets, [], [mul_basic, mul_slow_writes]},
-     {tps, [], [tps_16_bytes, tps_1K]}].
+     {tps, [], [tps_16_bytes, tps_1K]},
+     {port_exit_signal_race, [], [port_exit_monitor_race,
+                                  port_exit_demonitor_race,
+                                  port_exit_link_race,
+                                  port_exit_unlink_race,
+                                  port_exit_command_race,
+                                  port_exit_connect_race,
+                                  port_exit_close_race,
+                                  port_exit_exit_race,
+                                  port_exit_command_request_race,
+                                  port_exit_connect_request_race,
+                                  port_exit_close_request_race,
+                                  port_exit_control_request_race,
+                                  port_exit_call_request_race,
+                                  port_exit_info_request_race]}].
 
 init_per_testcase(Case, Config) when Case =:= mon_port_driver_die;
                                      Case =:= mon_port_driver_die_demonitor ->
@@ -2858,3 +2887,331 @@ port_is_monitored(Pid, PortName) when is_pid(Pid), is_atom(PortName) ->
                 end
         end,
     {proc_monitors, A, port_monitored_by, B}.
+
+%%
+%%
+%% Test cases testing for races when an exiting port receives a signal
+%% (port_exit_signal_race group).
+%%
+%%
+
+-record(esrt, {repeat = 1000,
+               owner_sched = 0,
+               prep_owner = fun (Prt) -> Prt end,
+               post_owner = fun (_) -> ok end,
+               send_sched_start = 0,
+               senders = 1,
+               prep_signal = fun (Prt, PrtOwn) -> {Prt, PrtOwn} end,
+               signal,
+               post_signal = fun (_) -> ok end}).
+
+port_exit_monitor_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PrtOwn}) ->
+                                       {Port, erlang:monitor(port, Port)}
+                               end,
+                      post_signal = fun ({Port, Mon}) ->
+                                            receive
+                                                {'DOWN', Mon, port, Port, Reason} ->
+                                                    if Reason == noproc -> ok;
+                                                       Reason == normal -> ok;
+                                                       true -> exit({unexpected_reason, Reason})
+                                                    end
+                                            after
+                                                1000 ->
+                                                    exit(missing_down_message)
+                                            end
+                                    end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_demonitor_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{prep_signal = fun (Port, _PrtOwn) ->
+                                            erlang:monitor(port, Port)
+                                    end,
+                      signal = fun (Mon) ->
+                                       erlang:demonitor(Mon, [flush])
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_link_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{prep_signal = fun (Port, _PrtOwn) ->
+                                            process_flag(trap_exit, true),
+                                            Port
+                                    end,
+                      signal = fun (Port) ->
+                                       link(Port),
+                                       Port
+                               end,
+                      post_signal = fun (Port) ->
+                                            receive
+                                                {'EXIT', Port, Reason} ->
+                                                    if Reason == noproc -> ok;
+                                                       Reason == normal -> ok;
+                                                       true -> exit({unexpected_reason, Reason})
+                                                    end
+                                            after
+                                                1000 ->
+                                                    exit(missing_exit_message)
+                                            end
+                                    end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_unlink_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{prep_signal = fun (Port, _PrtOwn) ->
+                                            process_flag(trap_exit, true),
+                                            link(Port),
+                                            Port
+                                    end,
+                      signal = fun (Port) ->
+                                       unlink(Port),
+                                       Port
+                               end,
+                      post_signal = fun (Port) ->
+                                            receive
+                                                {'EXIT', Port, Reason} ->
+                                                    if Reason == noproc -> ok;
+                                                       Reason == normal -> ok;
+                                                       true -> exit({unexpected_reason, Reason})
+                                                    end
+                                            after
+                                                0 ->
+                                                    ok
+                                            end
+                                    end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_command_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, PortOwner}) ->
+                                       Port ! {PortOwner, {command, "halloj"}},
+                                       Port
+                               end,
+                      post_signal = fun (Port) ->
+                                            receive
+                                                {Port, Data} ->
+                                                    {data, "halloj"} = Data
+                                            after
+                                                0 ->
+                                                    ok
+                                            end
+                                    end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_connect_race(Config) when is_list(Config) ->
+    %% We connect the port to the same port owner that it already has
+    %% otherwise we will get badsig issues since the owner close the
+    %% port as itself. The port owner will be spammed by {Port,
+    %% connected} messages but we ignore those...
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, PortOwner}) ->
+                                       Port ! {PortOwner, {connect, PortOwner}},
+                                       Port
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+
+port_exit_close_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, PortOwner}) ->
+                                       Port ! {PortOwner, close},
+                                       Port
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_exit_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PortOwner}) ->
+                                       exit(Port, normal)
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_command_request_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PortOwner}) ->
+                                       true = try
+                                                  erlang:port_command(Port, "hejsan")
+                                              catch
+                                                  error:badarg ->
+                                                      true
+                                              end,
+                                       Port
+                               end,
+                      post_signal = fun (Port) ->
+                                            receive
+                                                {Port, Data} ->
+                                                    {data, "hejsan"} = Data
+                                            after
+                                                0 ->
+                                                    ok
+                                            end
+                                    end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_connect_request_race(Config) when is_list(Config) ->
+    %% We connect the port to the same port owner that it already has
+    %% otherwise we will get badsig issues since the owner close the
+    %% port as itself.
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, PortOwner}) ->
+                                       true = try
+                                                  erlang:port_connect(Port, PortOwner)
+                                              catch
+                                                  error:badarg ->
+                                                      true
+                                              end
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_close_request_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PortOwner}) ->
+                                       true = try
+                                                  erlang:port_close(Port)
+                                              catch
+                                                  error:badarg ->
+                                                      true
+                                              end,
+                                       Port
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_control_request_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PortOwner}) ->
+                                       [] = try
+                                                erlang:port_control(Port, 0, [])
+                                            catch
+                                                error:badarg ->
+                                                    []
+                                            end
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_call_request_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, _PortOwner}) ->
+                                       [] = try
+                                                erlang:port_call(Port, 0, term_to_binary([]))
+                                            catch
+                                                error:badarg ->
+                                                    []
+                                            end
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+port_exit_info_request_race(Config) when is_list(Config) ->
+    ESRT0 = prepare_port_exit_signal_race_test(Config),
+    ESRT = ESRT0#esrt{signal = fun ({Port, PortOwner}) ->
+                                       case erlang:port_info(Port, connected) of
+                                           {connected, PortOwner} -> ok;
+                                           undefined -> ok;
+                                           Unexpected -> exit({unexpected_info, Unexpected})
+                                       end
+                               end},
+    repeat_port_exit_signal_race_test(ESRT).
+
+
+prepare_port_exit_signal_race_test(Config) ->
+    Path = proplists:get_value(data_dir, Config),
+    ok = load_driver(Path, "echo_drv"),
+    process_flag(scheduler, 1),
+    case erlang:system_info(schedulers_online) of
+        1 ->
+            #esrt{};
+        2 ->
+            #esrt{owner_sched = 2,
+                  send_sched_start = 1,
+                  senders = 1};
+        3 ->
+            #esrt{owner_sched = 2,
+                  send_sched_start = 3,
+                  senders = 1};
+        N ->
+            #esrt{owner_sched = 2,
+                  send_sched_start = 3,
+                  senders = N - 3}
+    end.
+
+repeat_port_exit_signal_race_test(#esrt{repeat = N} = ESRT) ->
+    repeat_port_exit_signal_race_test(N, ESRT).
+
+repeat_port_exit_signal_race_test(0, #esrt{}) ->
+    ok;
+repeat_port_exit_signal_race_test(N, #esrt{} = ESRT) ->
+    port_exit_signal_race_test(ESRT),
+    repeat_port_exit_signal_race_test(N-1, ESRT).
+
+port_exit_signal_race_test(#esrt{owner_sched = OwnSched,
+                                 prep_owner = PrepOwner,
+                                 post_owner = PostOwner,
+                                 send_sched_start = SendSchedStart,
+                                 senders = Senders,
+                                 prep_signal = PrepSignal,
+                                 signal = Signal,
+                                 post_signal = PostSignal}) ->
+    %% Send a close signal to the port simultaneously as another signal
+    %% is sent (from multiple senders). We try to provoke races between
+    %% the port entering an exiting state and handling of the signal. Such
+    %% races have shown themselves as either stray messages to signal
+    %% sender or runtime system crashes.
+    Parent = self(),
+    {PrtOwn,
+     PrtOwnMon} = spawn_opt(fun () ->
+                                    Prt = erlang:open_port({spawn_driver, "echo_drv"}, []),
+                                    true = is_port(Prt),
+                                    OwnState = PrepOwner(Prt),
+                                    Prt ! {self(), {command, "hej"}},
+                                    receive
+                                        {Prt, Data} ->
+                                            {data, "hej"} = Data
+                                    end,
+                                    Parent ! {prepared, self(), Prt},
+                                    receive {go, Parent} -> ok end,
+                                    Prt ! {self(), close},
+                                    PostOwner(OwnState)
+                            end,
+                            [link, monitor, {scheduler, OwnSched}]),
+    Port = receive {prepared, PrtOwn, Prt} -> Prt end,
+    PMs = lists:map(fun (SendSched) ->
+                            spawn_opt(fun () ->
+                                              PrtMon = erlang:monitor(port, Port),
+                                              SigState1 = PrepSignal(Port, PrtOwn),
+                                              Parent ! {prepared, self()},
+                                              receive {go, Parent} -> ok end,
+                                              SigState2 = Signal(SigState1),
+                                              receive {'DOWN', PrtMon, port, Port, _} -> ok end,
+                                              receive {bye, Parent} -> ok end,
+                                              PostSignal(SigState2),
+                                              receive Msg -> exit({unexpected_msg, Msg})
+                                              after 0 -> ok
+                                              end
+                                      end,
+                                      [link, monitor, {scheduler, SendSched}])
+                    end,
+                    lists:seq(SendSchedStart, SendSchedStart + Senders - 1)), 
+    lists:foreach(fun ({P, _M}) -> receive {prepared, P} -> ok end end, PMs),
+    PrtOwn ! {go, self()},
+    lists:foreach(fun ({P, _M}) -> P ! {go, self()} end, PMs),
+    receive
+        {'DOWN', PrtOwnMon, process, PrtOwn, OwnReason} ->
+            normal = OwnReason
+    end,
+    lists:foreach(fun ({P, _M}) -> P ! {bye, self()} end, PMs),
+    lists:foreach(fun ({P, M}) ->
+                          receive
+                              {'DOWN', M, process, P, SigSndReason} ->
+                                  normal = SigSndReason
+                          end
+                  end,
+                  PMs),
+    ok.
+
+%%
+%%
+%% End of test cases testing for races when an exiting port receives a signal
+%% (port_exit_signal_race group).
+%%
+%%
diff --git a/erts/emulator/test/port_SUITE_data/echo_drv.c b/erts/emulator/test/port_SUITE_data/echo_drv.c
index b4370f6455..22e8f09430 100644
--- a/erts/emulator/test/port_SUITE_data/echo_drv.c
+++ b/erts/emulator/test/port_SUITE_data/echo_drv.c
@@ -24,6 +24,9 @@ static ErlDrvSSizeT echo_control(ErlDrvData drv_data,
                                  ErlDrvSizeT len, char **rbuf, ErlDrvSizeT rlen);
 static void         echo_outputv(ErlDrvData drv_data, ErlIOVec *ev);
 static void         echo_drv_finish(void);
+static ErlDrvSSizeT echo_call(ErlDrvData drv_data, unsigned int command, char *buf,
+                              ErlDrvSizeT len, char **rbuf, ErlDrvSizeT rlen,
+                              unsigned int *flags);
 
 static ErlDrvEntry echo_drv_entry = { 
     NULL, /* init */
@@ -39,9 +42,9 @@ static ErlDrvEntry echo_drv_entry = {
     NULL, /* timeout */
     echo_outputv, /* outputv */
     NULL, /* ready_async */
-    NULL,
-    NULL,
-    NULL,
+    NULL, /* flush */
+    echo_call,
+    NULL, /* unused */
     ERL_DRV_EXTENDED_MARKER,
     ERL_DRV_EXTENDED_MAJOR_VERSION,
     ERL_DRV_EXTENDED_MINOR_VERSION,
@@ -103,6 +106,7 @@ static ErlDrvSSizeT echo_control(ErlDrvData drv_data,
                                  unsigned int command, char *buf,
                                  ErlDrvSizeT len, char **rbuf, ErlDrvSizeT rlen)
 {
+    *rbuf = NULL;
     return 0;
 }
 
@@ -110,3 +114,15 @@ static void echo_outputv(ErlDrvData drv_data, ErlIOVec *ev)
 {
     return;
 }
+
+static ErlDrvSSizeT echo_call(ErlDrvData drv_data, unsigned int command, char *buf,
+                              ErlDrvSizeT len, char **rbuf, ErlDrvSizeT rlen,
+                              unsigned int *flags)
+{
+    char *res_buf = driver_alloc(2);
+    /* Write NIL on external term format... */
+    res_buf[0] = 131;
+    res_buf[1] = 106;
+    *rbuf = res_buf;
+    return 2;
+}
-- 
2.31.1

openSUSE Build Service is sponsored by