[Git][ghc/ghc][master] No default finalizer exception handler

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Feb 16 19:10:15 UTC 2023



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


Commits:
681e0e8c by sheaf at 2023-02-16T14:09:56-05:00
No default finalizer exception handler

Commit cfc8e2e2 introduced a mechanism for handling of exceptions
that occur during Handle finalization, and 372cf730 set the default
handler to print out the error to stderr.

However, #21680 pointed out we might not want to set this by default,
as it might pollute users' terminals with unwanted information.
So, for the time being, the default handler discards the exception.

Fixes #21680

- - - - -


11 changed files:

- docs/users_guide/9.6.1-notes.rst
- libraries/base/GHC/TopHandler.hs
- libraries/base/changelog.md
- + libraries/base/tests/IO/T21336/FinalizerExceptionHandler.hs
- libraries/base/tests/IO/T21336/T21336a.hs
- libraries/base/tests/IO/T21336/T21336a.stderr
- libraries/base/tests/IO/T21336/T21336b.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T21336/T21336c.hs
- libraries/base/tests/IO/T21336/all.T
- − libraries/base/tests/T13167.stderr


Changes:

=====================================
docs/users_guide/9.6.1-notes.rst
=====================================
@@ -191,10 +191,9 @@ Runtime system
 ``base`` library
 ~~~~~~~~~~~~~~~~
 
-- Exceptions thrown by weak pointer finalizers are now caught and reported
-  via a global exception handler. By default this handler reports the error
-  to ``stderr`` although this can be changed using
-  ``GHC.Weak.Finalize.setFinalizerExceptionHandler``.
+- Exceptions thrown by weak pointer finalizers can now be reported by setting
+  a global exception handler, using ``GHC.Weak.Finalize.setFinalizerExceptionHandler``.
+  The default behaviour is unchanged (exceptions are ignored and not reported).
 
 - GHC now provides a set of operations for introspecting on the threads of a
   program, ``GHC.Conc.listThreads``, as well as operations for querying a thread's


=====================================
libraries/base/GHC/TopHandler.hs
=====================================
@@ -83,7 +83,11 @@ runMainIO main =
     do
       main_thread_id <- myThreadId
       weak_tid <- mkWeakThreadId main_thread_id
-      setFinalizerExceptionHandler handleFinalizerException
+
+    --setFinalizerExceptionHandler printToStderrFinalizerExceptionHandler
+      -- For the time being, we don't install any exception handler for
+      -- Handle finalization. Instead, the user should set one manually.
+
       case weak_tid of (Weak w) -> setMainThread w
       install_interrupt_handler $ do
            m <- deRefWeak weak_tid
@@ -253,13 +257,6 @@ flushStdHandles = do
       -- Swallow any exceptions thrown by the finalizer exception handler
       handleFinalizerExc se `catchException` (\(SomeException _) -> return ())
 
--- | See Note [Handling exceptions during Handle finalization] in
--- GHC.IO.Handle.Internals
-handleFinalizerException :: SomeException -> IO ()
-handleFinalizerException se =
-    hPutStr stderr msg `catchException` (\(SomeException _) -> return ())
-  where
-    msg = "Exception during Weak# finalization (ignored): " ++ displayException se ++ "\n"
 
 safeExit, fastExit :: Int -> IO a
 safeExit = exitHelper useSafeExit


=====================================
libraries/base/changelog.md
=====================================
@@ -12,10 +12,9 @@
   * Add `forall a. Functor (p a)` superclass for `Bifunctor p` ([CLC proposal #91](https://github.com/haskell/core-libraries-committee/issues/91))
   * Add Functor instances for `(,,,,) a b c d`, `(,,,,,) a b c d e` and
     `(,,,,,) a b c d e f`.
-  * Exceptions thrown by weak pointer finalizers are now reported via a global
-    exception handler.
-  * Add `GHC.Weak.Finalize.{get,set}FinalizerExceptionHandler` which allows the
-    user to override the above-mentioned handler.
+  * Exceptions thrown by weak pointer finalizers can now be reported by setting
+    a global exception handler, using `System.Mem.Weak.setFinalizerExceptionHandler`.
+    The default behaviour is unchanged (exceptions are ignored and not reported).
   * `Numeric.Natural` re-exports `GHC.Natural.minusNaturalMaybe`
     ([CLC proposal #45](https://github.com/haskell/core-libraries-committee/issues/45))
   * Add `Data.Foldable1` and `Data.Bifoldable1`


=====================================
libraries/base/tests/IO/T21336/FinalizerExceptionHandler.hs
=====================================
@@ -0,0 +1,21 @@
+module FinalizerExceptionHandler
+  ( setFinalizerExceptionHandler
+  , getFinalizerExceptionHandler
+  , printToStderrFinalizerExceptionHandler )
+  where
+
+import GHC.Exception     ( SomeException(..), displayException )
+import GHC.IO            ( catchException )
+import GHC.IO.Handle     ( hPutStr )
+import GHC.IO.StdHandles ( stderr )
+import GHC.Weak.Finalize ( setFinalizerExceptionHandler, getFinalizerExceptionHandler )
+
+-- | An exception handler for Handle finalization that prints the error to
+-- stderr, but doesn't rethrow it.
+printToStderrFinalizerExceptionHandler :: SomeException -> IO ()
+-- See Note [Handling exceptions during Handle finalization] in
+-- GHC.IO.Handle.Internals
+printToStderrFinalizerExceptionHandler se =
+    hPutStr stderr msg `catchException` (\(SomeException _) -> return ())
+  where
+    msg = "Exception during weak pointer finalization (ignored): " ++ displayException se ++ "\n"


=====================================
libraries/base/tests/IO/T21336/T21336a.hs
=====================================
@@ -1,9 +1,10 @@
-import GHC.Weak
 import System.IO
 import System.Mem
+import FinalizerExceptionHandler
 
 main :: IO ()
 main = do
+    setFinalizerExceptionHandler printToStderrFinalizerExceptionHandler
     f <- openFile "/dev/full" WriteMode
     hPutStr f "hello"
     -- Ensure that the Handle's finalizer is run


=====================================
libraries/base/tests/IO/T21336/T21336a.stderr
=====================================
@@ -1 +1 @@
-Exception during Weak# finalization (ignored): GHC.IO.FD.fdWrite: resource exhausted (No space left on device)
+Exception during weak pointer finalization (ignored): GHC.IO.FD.fdWrite: resource exhausted (No space left on device)


=====================================
libraries/base/tests/IO/T21336/T21336b.hs
=====================================
@@ -1,6 +1,9 @@
-import GHC.Weak
 import System.IO
+import System.Mem
+import FinalizerExceptionHandler
 
 main :: IO ()
-main = hPutStr stdout "hello"
+main = do
+  setFinalizerExceptionHandler printToStderrFinalizerExceptionHandler
+  hPutStr stdout "hello"
 


=====================================
libraries/base/tests/IO/T21336/T21336b.stderr
=====================================
@@ -1 +1 @@
-Exception during Weak# finalization (ignored): <stdout>: hFlush: resource exhausted (No space left on device)
+Exception during weak pointer finalization (ignored): <stdout>: hFlush: resource exhausted (No space left on device)


=====================================
libraries/base/tests/IO/T21336/T21336c.hs
=====================================
@@ -1,6 +1,9 @@
-import GHC.Weak
 import System.IO
+import System.Mem
+import FinalizerExceptionHandler
 
 main :: IO ()
-main = hPutStr stdout "hello"
+main = do
+  setFinalizerExceptionHandler printToStderrFinalizerExceptionHandler
+  hPutStr stdout "hello"
 


=====================================
libraries/base/tests/IO/T21336/all.T
=====================================
@@ -3,14 +3,18 @@ test('T21336a',
      [ unless(opsys('linux') or opsys('freebsd'), skip)
      , js_broken(22261)
      , fragile(22022)
+     , extra_files(['FinalizerExceptionHandler.hs'])
      ],
      compile_and_run, [''])
 test('T21336b',
-     [unless(opsys('linux') or opsys('freebsd'), skip), js_broken(22352)],
+     [ unless(opsys('linux') or opsys('freebsd'), skip)
+     , js_broken(22352)
+     , extra_files(['FinalizerExceptionHandler.hs'])
+     ],
      makefile_test, [])
 test('T21336c',
      [ unless(opsys('linux') or opsys('freebsd'), skip)
      , js_broken(22370)
+     , extra_files(['FinalizerExceptionHandler.hs'])
      ],
      makefile_test, [])
-


=====================================
libraries/base/tests/T13167.stderr deleted
=====================================
@@ -1,4 +0,0 @@
-Exception during Weak# finalization (ignored): failed
-Exception during Weak# finalization (ignored): failed
-Exception during Weak# finalization (ignored): failed
-Exception during Weak# finalization (ignored): failed



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/681e0e8ce470ec77a0db071f9fc7ec15995a0bb3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/681e0e8ce470ec77a0db071f9fc7ec15995a0bb3
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/20230216/083748ce/attachment-0001.html>


More information about the ghc-commits mailing list