[Git][ghc/ghc][master] compiler: don't install signal handlers when the host platform doesn't have signals

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Apr 24 16:20:35 UTC 2023



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


Commits:
2685a12d by Cheng Shao at 2023-04-24T12:20:21-04:00
compiler: don't install signal handlers when the host platform doesn't have signals

Previously, large parts of GHC API will transitively invoke
withSignalHandlers, which doesn't work on host platforms without
signal functionality at all (e.g. wasm32-wasi). By making
withSignalHandlers a no-op on those platforms, we can make more parts
of GHC API work out of the box when signals aren't supported.

- - - - -


1 changed file:

- compiler/GHC/Utils/Panic.hs


Changes:

=====================================
compiler/GHC/Utils/Panic.hs
=====================================
@@ -7,6 +7,8 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE ScopedTypeVariables, LambdaCase #-}
 
+#include <ghcautoconf.h>
+
 -- | Defines basic functions for printing error messages.
 --
 -- It's hard to put these functions anywhere else without causing
@@ -236,6 +238,11 @@ signalHandlersRefCount = unsafePerformIO $ newMVar (0,Nothing)
 -- | Temporarily install standard signal handlers for catching ^C, which just
 -- throw an exception in the current thread.
 withSignalHandlers :: ExceptionMonad m => m a -> m a
+#if !defined(HAVE_SIGNAL_H)
+-- No signal functionality exist on the host platform (e.g. on
+-- wasm32-wasi), so don't attempt to set up signal handlers
+withSignalHandlers = id
+#else
 withSignalHandlers act = do
   main_thread <- liftIO myThreadId
   wtid <- liftIO (mkWeakThreadId main_thread)
@@ -295,6 +302,7 @@ withSignalHandlers act = do
 
   mayInstallHandlers
   act `MC.finally` mayUninstallHandlers
+#endif
 
 callStackDoc :: HasCallStack => SDoc
 callStackDoc = prettyCallStackDoc callStack



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2685a12d462573ce23ef7f4356a2f8c95ef63e1d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2685a12d462573ce23ef7f4356a2f8c95ef63e1d
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/20230424/7eee4ca5/attachment-0001.html>


More information about the ghc-commits mailing list