File 0994-erts-poll-port-process-exit.patch of Package erlang

From d710c4540bfb852a93951f32df99d5294c74cfb1 Mon Sep 17 00:00:00 2001
From: yastanotheruser <alvarezpcuser@gmail.com>
Date: Sat, 30 Mar 2024 00:05:08 -0500
Subject: [PATCH 1/2] erts: poll port process exit

Poll process handle as an special case of input. This allows
reliable detection of process termination, thus fixing an error
case on Windows where the exit_status message never was sent if
the process closed its stdout before exiting.

Closes #8317
---
 erts/emulator/sys/win32/sys.c | 61 +++++++++++++++++++++++++++++------
 1 file changed, 51 insertions(+), 10 deletions(-)

diff --git a/erts/emulator/sys/win32/sys.c b/erts/emulator/sys/win32/sys.c
index c701db1b7b..7f4f4efcd0 100644
--- a/erts/emulator/sys/win32/sys.c
+++ b/erts/emulator/sys/win32/sys.c
@@ -883,6 +883,14 @@ set_driver_data(DriverData* dp, HANDLE ifd, HANDLE ofd, int read_write, int repo
 			       ERL_DRV_WRITE|ERL_DRV_USE, 1);
 	ASSERT(result != -1);
     }
+
+    /* Get "input" from process handle when it exits. */
+    if (dp->report_exit && dp->port_pid != INVALID_HANDLE_VALUE) {
+	result = driver_select(dp->port_num, (ErlDrvEvent)dp->port_pid,
+			       ERL_DRV_READ|ERL_DRV_USE, 1);
+	ASSERT(result != -1);
+    }
+
     return (ErlDrvData) dp;
 }
 
@@ -2290,6 +2298,11 @@ stop(ErlDrvData data)
 			     (ErlDrvEvent)dp->out.ov.hEvent,
 			     ERL_DRV_WRITE|ERL_DRV_USE_NO_CALLBACK, 0);
     }    
+    if (dp->report_exit) {
+	(void) driver_select(dp->port_num,
+			     (ErlDrvEvent)dp->port_pid,
+			     ERL_DRV_READ|ERL_DRV_USE_NO_CALLBACK, 0);
+    }
 
     if (dp->out.thread == (HANDLE) -1 && dp->in.thread == (HANDLE) -1) {
 	release_driver_data(dp);
@@ -2542,11 +2555,45 @@ ready_input(ErlDrvData drv_data, ErlDrvEvent ready_event)
     DriverData* dp = (DriverData *) drv_data;
     int pb;
 
+    DEBUGF(("ready_input: dp %p, event 0x%x\n", dp, ready_event));
+
+    /*
+     * Port process exit.
+     */
+
+    if (ready_event == (ErlDrvEvent) dp->port_pid) {
+	DWORD exitcode;
+
+	if (GetExitCodeProcess(dp->port_pid, &exitcode)) {
+	    ASSERT(exitcode != STILL_ACTIVE);
+	    driver_report_exit(dp->port_num, exitcode);
+	}
+
+	{
+	    erts_aint32_t state;
+	    Port *prt = erts_drvport2port_state(dp->port_num, &state);
+
+	    /*
+	     * Stop polling process handle, otherwise we'll still
+	     * get "input" from it.
+	     */
+
+	    if (prt != ERTS_INVALID_ERL_DRV_PORT &&
+		(state & ERTS_PORT_SFLG_SOFT_EOF)) {
+		(void) driver_select(dp->port_num,
+				     (ErlDrvEvent)dp->port_pid,
+				     ERL_DRV_READ|ERL_DRV_USE_NO_CALLBACK, 0);
+	    }
+	}
+
+	driver_failure_eof(dp->port_num);
+	return;
+    }
+
     pb = dp->packet_bytes;
     if(dp->in.thread == (HANDLE) -1) {
 	dp->in.async_io_active = 0;
     }
-    DEBUGF(("ready_input: dp %p, event 0x%x\n", dp, ready_event));
 
     /*
      * Evaluate the result of the overlapped read.
@@ -2682,15 +2729,9 @@ ready_input(ErlDrvData drv_data, ErlDrvEvent ready_event)
     } else {
 	DEBUGF(("ready_input(): error: %s\n", win32_errorstr(error)));
 	if (error == ERROR_BROKEN_PIPE || error == ERROR_HANDLE_EOF) {
-	    /* Maybe check exit status */
-	    if (dp->report_exit) {
-		DWORD exitcode;
-		if (GetExitCodeProcess(dp->port_pid, &exitcode) &&
-		    exitcode != STILL_ACTIVE) {
-		    driver_report_exit(dp->port_num, exitcode);
-		}
-	    }
-	    driver_failure_eof(dp->port_num);
+	    /* Don't repeat this call when reporting exit. */
+	    if (!dp->report_exit || dp->port_pid == INVALID_HANDLE_VALUE)
+		driver_failure_eof(dp->port_num);
 	} else {			/* Report real errors. */
 	    int error = GetLastError();
 
-- 
2.35.3

openSUSE Build Service is sponsored by