[Git][ghc/ghc][master] Move pthread and timerfd ticker implementations to separate files

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Feb 3 10:24:26 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
2931712a by Wander Hillen at 2023-02-03T05:24:06-05:00
Move pthread and timerfd ticker implementations to separate files

- - - - -


3 changed files:

- rts/posix/Ticker.c
- rts/posix/ticker/Pthread.c
- + rts/posix/ticker/TimerFd.c


Changes:

=====================================
rts/posix/Ticker.c
=====================================
@@ -65,13 +65,17 @@
  * On Linux we can use timerfd_* (introduced in Linux
  * 2.6.25) and a thread instead of alarm signals. It avoids the risk of
  * interrupting syscalls (see #10840) and the risk of being accidentally
- * modified in user code using signals.
+ * modified in user code using signals. NetBSD has also added timerfd
+ * support since version 10.
+ *
+ * For older version of linux/netbsd without timerfd we fall back to the
+ * pthread based implementation.
  */
-#if defined(linux_HOST_OS) && HAVE_SYS_TIMERFD_H
-#define USE_PTHREAD_FOR_ITIMER
+#if HAVE_SYS_TIMERFD_H
+#define USE_TIMERFD_FOR_ITIMER
 #endif
 
-#if defined(freebsd_HOST_OS)
+#if defined(linux_HOST_OS)
 #define USE_PTHREAD_FOR_ITIMER
 #endif
 
@@ -79,6 +83,10 @@
 #define USE_PTHREAD_FOR_ITIMER
 #endif
 
+#if defined(freebsd_HOST_OS)
+#define USE_PTHREAD_FOR_ITIMER
+#endif
+
 #if defined(solaris2_HOST_OS)
 /* USE_TIMER_CREATE is usually disabled for Solaris. In fact it is
    supported well on this OS, but requires additional privilege. When
@@ -98,7 +106,9 @@ ghc-stage2: timer_create: Not owner
 #endif /* solaris2_HOST_OS */
 
 // Select the variant to use
-#if defined(USE_PTHREAD_FOR_ITIMER)
+#if defined(USE_TIMERFD_FOR_ITIMER)
+#include "ticker/TimerFd.c"
+#elif defined(USE_PTHREAD_FOR_ITIMER)
 #include "ticker/Pthread.c"
 #elif defined(USE_TIMER_CREATE)
 #include "ticker/TimerCreate.c"


=====================================
rts/posix/ticker/Pthread.c
=====================================
@@ -63,13 +63,6 @@
 #include <unistd.h>
 #include <fcntl.h>
 
-#if defined(HAVE_SYS_TIMERFD_H)
-#include <sys/timerfd.h>
-#define USE_TIMERFD_FOR_ITIMER 1
-#else
-#define USE_TIMERFD_FOR_ITIMER 0
-#endif
-
 /*
  * TFD_CLOEXEC has been added in Linux 2.6.26.
  * If it is not available, we use fcntl(F_SETFD).
@@ -93,61 +86,16 @@ static Condition start_cond;
 static Mutex mutex;
 static OSThreadId thread;
 
-// file descriptor for the timer (Linux only)
-static int timerfd = -1;
-
-// pipe for signaling exit
-static int pipefds[2];
-
 static void *itimer_thread_func(void *_handle_tick)
 {
     TickProc handle_tick = _handle_tick;
-    uint64_t nticks;
-    ssize_t r = 0;
-    struct pollfd pollfds[2];
-
-#if USE_TIMERFD_FOR_ITIMER
-    pollfds[0].fd = pipefds[0];
-    pollfds[0].events = POLLIN;
-    pollfds[1].fd = timerfd;
-    pollfds[1].events = POLLIN;
-#endif
 
     // Relaxed is sufficient: If we don't see that exited was set in one iteration we will
     // see it next time.
     TSAN_ANNOTATE_BENIGN_RACE(&exited, "itimer_thread_func");
     while (!RELAXED_LOAD(&exited)) {
-        if (USE_TIMERFD_FOR_ITIMER) {
-            if (poll(pollfds, 2, -1) == -1) {
-                sysErrorBelch("Ticker: poll failed: %s", strerror(errno));
-            }
-
-            // We check the pipe first, even though the timerfd may also have triggered.
-            if (pollfds[0].revents & POLLIN) {
-                // the pipe is ready for reading, the only possible reason is that we're exiting
-                exited = true; // set this again to make sure even RELAXED_LOAD will read the proper value
-                // no further action needed, skip ahead to handling the final tick and then stopping
-            }
-            else if (pollfds[1].revents & POLLIN) { // the timerfd is ready for reading
-                r = read(timerfd, &nticks, sizeof(nticks)); // this should never block now
-
-                if ((r == 0) && (errno == 0)) {
-                   /* r == 0 is expected only for non-blocking fd (in which case
-                    * errno should be EAGAIN) but we use a blocking fd.
-                    *
-                    * Due to a kernel bug (cf https://lkml.org/lkml/2019/8/16/335)
-                    * on some platforms we could see r == 0 and errno == 0.
-                    */
-                   IF_DEBUG(scheduler, debugBelch("read(timerfd) returned 0 with errno=0. This is a known kernel bug. We just ignore it."));
-                }
-                else if (r != sizeof(nticks) && errno != EINTR) {
-                   barf("Ticker: read(timerfd) failed with %s and returned %zd", strerror(errno), r);
-                }
-            }
-        } else {
-            if (rtsSleep(itimer_interval) != 0) {
-                sysErrorBelch("Ticker: sleep failed: %s", strerror(errno));
-            }
+        if (rtsSleep(itimer_interval) != 0) {
+            sysErrorBelch("Ticker: sleep failed: %s", strerror(errno));
         }
 
         // first try a cheap test
@@ -164,10 +112,6 @@ static void *itimer_thread_func(void *_handle_tick)
         }
     }
 
-    if (USE_TIMERFD_FOR_ITIMER) {
-        close(timerfd);
-    }
-
     return NULL;
 }
 
@@ -186,39 +130,6 @@ initTicker (Time interval, TickProc handle_tick)
     initCondition(&start_cond);
     initMutex(&mutex);
 
-    /* Open the file descriptor for the timer synchronously.
-     *
-     * We used to do it in itimer_thread_func (i.e. in the timer thread) but it
-     * meant that some user code could run before it and get confused by the
-     * allocation of the timerfd.
-     *
-     * See hClose002 which unsafely closes a file descriptor twice expecting an
-     * exception the second time: it sometimes failed when the second call to
-     * "close" closed our own timerfd which inadvertently reused the same file
-     * descriptor closed by the first call! (see #20618)
-     */
-#if USE_TIMERFD_FOR_ITIMER
-    struct itimerspec it;
-    it.it_value.tv_sec  = TimeToSeconds(itimer_interval);
-    it.it_value.tv_nsec = TimeToNS(itimer_interval) % 1000000000;
-    it.it_interval = it.it_value;
-
-    timerfd = timerfd_create(CLOCK_MONOTONIC, TFD_CLOEXEC);
-    if (timerfd == -1) {
-        barf("timerfd_create: %s", strerror(errno));
-    }
-    if (!TFD_CLOEXEC) {
-        fcntl(timerfd, F_SETFD, FD_CLOEXEC);
-    }
-    if (timerfd_settime(timerfd, 0, &it, NULL)) {
-        barf("timerfd_settime: %s", strerror(errno));
-    }
-
-    if (pipe(pipefds) < 0) {
-        barf("pipe: %s", strerror(errno));
-    }
-#endif
-
     /*
      * Create the thread with all blockable signals blocked, leaving signal
      * handling to the main and/or other threads.  This is especially useful in
@@ -269,21 +180,9 @@ exitTicker (bool wait)
 
     // wait for ticker to terminate if necessary
     if (wait) {
-#if USE_TIMERFD_FOR_ITIMER
-        // write anything to the pipe to trigger poll() in the ticker thread
-        if (write(pipefds[1], "stop", 5) < 0) {
-            sysErrorBelch("Ticker: Failed to write to pipe: %s", strerror(errno));
-        }
-#endif
         if (pthread_join(thread, NULL)) {
             sysErrorBelch("Ticker: Failed to join: %s", strerror(errno));
         }
-#if USE_TIMERFD_FOR_ITIMER
-        // These need to happen AFTER the ticker thread has finished to prevent a race condition
-        // where the ticker thread closes the read end of the pipe before we're done writing to it.
-        close(pipefds[0]);
-        close(pipefds[1]);
-#endif
         closeMutex(&mutex);
         closeCondition(&start_cond);
     } else {


=====================================
rts/posix/ticker/TimerFd.c
=====================================
@@ -0,0 +1,280 @@
+/* -----------------------------------------------------------------------------
+ *
+ * (c) The GHC Team, 1995-2023
+ *
+ * Interval timer for profiling and pre-emptive scheduling.
+ *
+ * ---------------------------------------------------------------------------*/
+
+/*
+ * We use a realtime timer by default.  I found this much more
+ * reliable than a CPU timer:
+ *
+ * Experiments with different frequencies: using
+ * CLOCK_REALTIME/CLOCK_MONOTONIC on Linux 2.6.32,
+ *     1000us has  <1% impact on runtime
+ *      100us has  ~2% impact on runtime
+ *       10us has ~40% impact on runtime
+ *
+ * using CLOCK_PROCESS_CPUTIME_ID on Linux 2.6.32,
+ *     I cannot get it to tick faster than 10ms (10000us)
+ *     which isn't great for profiling.
+ *
+ * In the threaded RTS, we can't tick in CPU time because the thread
+ * which has the virtual timer might be idle, so the tick would never
+ * fire.  Therefore we used to tick in realtime in the threaded RTS and
+ * in CPU time otherwise, but now we always tick in realtime, for
+ * several reasons:
+ *
+ *   - resolution (see above)
+ *   - consistency (-threaded is the same as normal)
+ *   - more consistency: Windows only has a realtime timer
+ *
+ * Note we want to use CLOCK_MONOTONIC rather than CLOCK_REALTIME,
+ * because the latter may jump around (NTP adjustments, leap seconds
+ * etc.).
+ */
+
+#include "rts/PosixSource.h"
+#include "Rts.h"
+
+#include "Ticker.h"
+#include "RtsUtils.h"
+#include "Proftimer.h"
+#include "Schedule.h"
+#include "posix/Clock.h"
+#include <sys/poll.h>
+
+#include <time.h>
+#if HAVE_SYS_TIME_H
+# include <sys/time.h>
+#endif
+
+#if defined(HAVE_SIGNAL_H)
+# include <signal.h>
+#endif
+
+#include <string.h>
+
+#include <pthread.h>
+#if defined(HAVE_PTHREAD_NP_H)
+#include <pthread_np.h>
+#endif
+#include <unistd.h>
+#include <fcntl.h>
+
+#include <sys/timerfd.h>
+
+
+/*
+ * TFD_CLOEXEC has been added in Linux 2.6.26.
+ * If it is not available, we use fcntl(F_SETFD).
+ */
+#if !defined(TFD_CLOEXEC)
+#define TFD_CLOEXEC 0
+#endif
+
+static Time itimer_interval = DEFAULT_TICK_INTERVAL;
+
+// Should we be firing ticks?
+// Writers to this must hold the mutex below.
+static bool stopped = false;
+
+// should the ticker thread exit?
+// This can be set without holding the mutex.
+static bool exited = true;
+
+// Signaled when we want to (re)start the timer
+static Condition start_cond;
+static Mutex mutex;
+static OSThreadId thread;
+
+// file descriptor for the timer (Linux only)
+static int timerfd = -1;
+
+// pipe for signaling exit
+static int pipefds[2];
+
+static void *itimer_thread_func(void *_handle_tick)
+{
+    TickProc handle_tick = _handle_tick;
+    uint64_t nticks;
+    ssize_t r = 0;
+    struct pollfd pollfds[2];
+
+    pollfds[0].fd = pipefds[0];
+    pollfds[0].events = POLLIN;
+    pollfds[1].fd = timerfd;
+    pollfds[1].events = POLLIN;
+
+    // Relaxed is sufficient: If we don't see that exited was set in one iteration we will
+    // see it next time.
+    TSAN_ANNOTATE_BENIGN_RACE(&exited, "itimer_thread_func");
+    while (!RELAXED_LOAD(&exited)) {
+        if (poll(pollfds, 2, -1) == -1) {
+            sysErrorBelch("Ticker: poll failed: %s", strerror(errno));
+        }
+
+        // We check the pipe first, even though the timerfd may also have triggered.
+        if (pollfds[0].revents & POLLIN) {
+            // the pipe is ready for reading, the only possible reason is that we're exiting
+            exited = true; // set this again to make sure even RELAXED_LOAD will read the proper value
+            // no further action needed, skip ahead to handling the final tick and then stopping
+        }
+        else if (pollfds[1].revents & POLLIN) { // the timerfd is ready for reading
+            r = read(timerfd, &nticks, sizeof(nticks)); // this should never block now
+
+            if ((r == 0) && (errno == 0)) {
+               /* r == 0 is expected only for non-blocking fd (in which case
+                * errno should be EAGAIN) but we use a blocking fd.
+                *
+                * Due to a kernel bug (cf https://lkml.org/lkml/2019/8/16/335)
+                * on some platforms we could see r == 0 and errno == 0.
+                */
+               IF_DEBUG(scheduler, debugBelch("read(timerfd) returned 0 with errno=0. This is a known kernel bug. We just ignore it."));
+            }
+            else if (r != sizeof(nticks) && errno != EINTR) {
+               barf("Ticker: read(timerfd) failed with %s and returned %zd", strerror(errno), r);
+            }
+        }
+
+        // first try a cheap test
+        TSAN_ANNOTATE_BENIGN_RACE(&stopped, "itimer_thread_func");
+        if (RELAXED_LOAD(&stopped)) {
+            OS_ACQUIRE_LOCK(&mutex);
+            // should we really stop?
+            if (stopped) {
+                waitCondition(&start_cond, &mutex);
+            }
+            OS_RELEASE_LOCK(&mutex);
+        } else {
+            handle_tick(0);
+        }
+    }
+
+    close(timerfd);
+    return NULL;
+}
+
+void
+initTicker (Time interval, TickProc handle_tick)
+{
+    itimer_interval = interval;
+    stopped = true;
+    exited = false;
+#if defined(HAVE_SIGNAL_H)
+    sigset_t mask, omask;
+    int sigret;
+#endif
+    int ret;
+
+    initCondition(&start_cond);
+    initMutex(&mutex);
+
+    /* Open the file descriptor for the timer synchronously.
+     *
+     * We used to do it in itimer_thread_func (i.e. in the timer thread) but it
+     * meant that some user code could run before it and get confused by the
+     * allocation of the timerfd.
+     *
+     * See hClose002 which unsafely closes a file descriptor twice expecting an
+     * exception the second time: it sometimes failed when the second call to
+     * "close" closed our own timerfd which inadvertently reused the same file
+     * descriptor closed by the first call! (see #20618)
+     */
+    struct itimerspec it;
+    it.it_value.tv_sec  = TimeToSeconds(itimer_interval);
+    it.it_value.tv_nsec = TimeToNS(itimer_interval) % 1000000000;
+    it.it_interval = it.it_value;
+
+    timerfd = timerfd_create(CLOCK_MONOTONIC, TFD_CLOEXEC);
+    if (timerfd == -1) {
+        barf("timerfd_create: %s", strerror(errno));
+    }
+    if (!TFD_CLOEXEC) {
+        fcntl(timerfd, F_SETFD, FD_CLOEXEC);
+    }
+    if (timerfd_settime(timerfd, 0, &it, NULL)) {
+        barf("timerfd_settime: %s", strerror(errno));
+    }
+
+    if (pipe(pipefds) < 0) {
+        barf("pipe: %s", strerror(errno));
+    }
+
+    /*
+     * Create the thread with all blockable signals blocked, leaving signal
+     * handling to the main and/or other threads.  This is especially useful in
+     * the non-threaded runtime, where applications might expect sigprocmask(2)
+     * to effectively block signals.
+     */
+#if defined(HAVE_SIGNAL_H)
+    sigfillset(&mask);
+    sigret = pthread_sigmask(SIG_SETMASK, &mask, &omask);
+#endif
+    ret = createAttachedOSThread(&thread, "ghc_ticker", itimer_thread_func, (void*)handle_tick);
+#if defined(HAVE_SIGNAL_H)
+    if (sigret == 0)
+        pthread_sigmask(SIG_SETMASK, &omask, NULL);
+#endif
+
+    if (ret != 0) {
+        barf("Ticker: Failed to spawn thread: %s", strerror(errno));
+    }
+}
+
+void
+startTicker(void)
+{
+    OS_ACQUIRE_LOCK(&mutex);
+    RELAXED_STORE(&stopped, false);
+    signalCondition(&start_cond);
+    OS_RELEASE_LOCK(&mutex);
+}
+
+/* There may be at most one additional tick fired after a call to this */
+void
+stopTicker(void)
+{
+    OS_ACQUIRE_LOCK(&mutex);
+    RELAXED_STORE(&stopped, true);
+    OS_RELEASE_LOCK(&mutex);
+}
+
+/* There may be at most one additional tick fired after a call to this */
+void
+exitTicker (bool wait)
+{
+    ASSERT(!SEQ_CST_LOAD(&exited));
+    SEQ_CST_STORE(&exited, true);
+    // ensure that ticker wakes up if stopped
+    startTicker();
+
+    // wait for ticker to terminate if necessary
+    if (wait) {
+        // write anything to the pipe to trigger poll() in the ticker thread
+        if (write(pipefds[1], "stop", 5) < 0) {
+            sysErrorBelch("Ticker: Failed to write to pipe: %s", strerror(errno));
+        }
+
+        if (pthread_join(thread, NULL)) {
+            sysErrorBelch("Ticker: Failed to join: %s", strerror(errno));
+        }
+
+        // These need to happen AFTER the ticker thread has finished to prevent a race condition
+        // where the ticker thread closes the read end of the pipe before we're done writing to it.
+        close(pipefds[0]);
+        close(pipefds[1]);
+
+        closeMutex(&mutex);
+        closeCondition(&start_cond);
+    } else {
+        pthread_detach(thread);
+    }
+}
+
+int
+rtsTimerSignal(void)
+{
+    return SIGALRM;
+}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2931712a127423c0ab7ac94c7d96dfa8d6c446b6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2931712a127423c0ab7ac94c7d96dfa8d6c446b6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230203/bea34527/attachment-0001.html>


More information about the ghc-commits mailing list