[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: No default finalizer exception handler

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Feb 16 22:42:31 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job 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

- - - - -
b3ac17ad by Matthew Pickering at 2023-02-16T14:10:31-05:00
unicode: Don't inline bitmap in generalCategory

generalCategory contains a huge literal string but is marked INLINE,
this will duplicate the string into any use site of generalCategory. In
particular generalCategory is used in functions like isSpace and the
literal gets inlined into this function which makes it massive.

https://github.com/haskell/core-libraries-committee/issues/130

Fixes #22949

-------------------------
Metric Decrease:
    T4029
    T18304
-------------------------

- - - - -
2b661c03 by sheaf at 2023-02-16T17:42:19-05:00
Expand synonyms in RoughMap

We were failing to expand type synonyms in the function
GHC.Core.RoughMap.typeToRoughMatchLookupTc, even though the
RoughMap infrastructure crucially relies on type synonym expansion
to work.

This patch adds the missing type-synonym expansion.

Fixes #22985

- - - - -
b7c2ff74 by Matthew Pickering at 2023-02-16T17:42:20-05:00
ghcup-metadata: Add test artifact

Add the released testsuite tarball to the generated ghcup metadata.

- - - - -
dcd637ee by Matthew Pickering at 2023-02-16T17:42:20-05:00
ghcup-metadata: Use Ubuntu and Rocky bindists

Prefer to use the Ubuntu 20.04 and 18.04 binary distributions on Ubuntu
and Linux Mint. Prefer to use the Rocky 8 binary distribution on
unknown distributions.

- - - - -


19 changed files:

- .gitlab-ci.yml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Core/RoughMap.hs
- docs/users_guide/9.6.1-notes.rst
- libraries/base/GHC/TopHandler.hs
- libraries/base/GHC/Unicode/Internal/Char/UnicodeData/GeneralCategory.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
- libraries/base/tools/ucd2haskell/exe/Parser/Text.hs
- + testsuite/tests/typecheck/should_compile/T22985a.hs
- + testsuite/tests/typecheck/should_compile/T22985b.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1011,6 +1011,12 @@ ghcup-metadata-nightly:
       artifacts: false
     - job: nightly-x86_64-linux-centos7-validate
       artifacts: false
+    - job: nightly-x86_64-linux-ubuntu20_04-validate
+      artifacts: false
+    - job: nightly-x86_64-linux-ubuntu18_04-validate
+      artifacts: false
+    - job: nightly-x86_64-linux-rocky8-validate
+      artifacts: false
     - job: nightly-x86_64-darwin-validate
       artifacts: false
     - job: nightly-aarch64-darwin-validate


=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -73,6 +73,7 @@ class PlatformSpec(NamedTuple):
     subdir: str
 
 source_artifact = Artifact('source-tarball', 'ghc-{version}-src.tar.xz', 'ghc-{version}' )
+test_artifact = Artifact('source-tarball', 'ghc-{version}-testsuite.tar.xz', 'ghc-{version}' )
 
 def debian(arch, n):
     return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
@@ -93,6 +94,12 @@ def fedora(n):
 def alpine(n):
     return linux_platform("x86_64", "x86_64-linux-alpine{n}".format(n=n))
 
+def rocky(n):
+    return linux_platform("x86_64", "x86_64-linux-rocky{n}".format(n=n))
+
+def ubuntu(n):
+    return linux_platform("x86_64", "x86_64-linux-ubuntu{n}".format(n=n))
+
 def linux_platform(arch, opsys):
     return PlatformSpec( opsys, 'ghc-{version}-{arch}-unknown-linux'.format(version="{version}", arch=arch) )
 
@@ -156,6 +163,9 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
         eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name))))
         return mk_one_metadata(release_mode, version, job_map, mk_from_platform(pipeline_type, platform))
 
+    ubuntu1804 = mk(ubuntu("18_04"))
+    ubuntu2004 = mk(ubuntu("20_04"))
+    rocky8 = mk(rocky("8"))
     # Here are all the bindists we can distribute
     centos7 = mk(centos(7))
     fedora33 = mk(fedora(33))
@@ -170,6 +180,7 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
     deb9_i386 = mk(debian("i386", 9))
 
     source = mk_one_metadata(release_mode, version, job_map, source_artifact)
+    test = mk_one_metadata(release_mode, version, job_map, test_artifact)
 
     # The actual metadata, this is not a precise science, but just what the ghcup
     # developers want.
@@ -178,18 +189,18 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
                            , "(>= 10 && < 11)": deb10
                            , ">= 11": deb11
                            , "unknown_versioning": deb11 }
-          , "Linux_Ubuntu" : { "unknown_versioning": deb10
-                             , "( >= 16 && < 19 )": deb9
+          , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004
+                             , "( >= 16 && < 19 )": ubuntu1804
                              }
-          , "Linux_Mint"   : { "< 20": deb9
-                             , ">= 20": deb10 }
+          , "Linux_Mint"   : { "< 20": ubuntu1804
+                             , ">= 20": ubuntu2004 }
           , "Linux_CentOS"  : { "( >= 7 && < 8 )" : centos7
                               , "unknown_versioning" : centos7  }
           , "Linux_Fedora"  : { ">= 33": fedora33
                               , "unknown_versioning": centos7 }
           , "Linux_RedHat"  : { "unknown_versioning": centos7 }
           #MP: Replace here with Rocky8 when that job is in the pipeline
-          , "Linux_UnknownLinux" : { "unknown_versioning": fedora33 }
+          , "Linux_UnknownLinux" : { "unknown_versioning": rocky8 }
           , "Darwin" : { "unknown_versioning" : darwin_x86 }
           , "Windows" : { "unknown_versioning" :  windows }
           , "Linux_Alpine" : { "unknown_versioning": alpine3_12 }
@@ -220,6 +231,7 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
         # Check that this link exists
         , "viChangeLog": change_log
         , "viSourceDL": source
+        , "viTestDL": test
         , "viArch": { "A_64": a64
                     , "A_32": a32
                     , "A_ARM64": arm64


=====================================
compiler/GHC/Core/RoughMap.hs
=====================================
@@ -320,7 +320,11 @@ roughMatchTcsLookup tys = map typeToRoughMatchLookupTc tys
 
 typeToRoughMatchLookupTc :: Type -> RoughMatchLookupTc
 typeToRoughMatchLookupTc ty
-  | Just (ty', _) <- splitCastTy_maybe ty
+  -- Expand synonyms first, as explained in Note [Rough matching in class and family instances].
+  -- Failing to do so led to #22985.
+  | Just ty' <- coreView ty
+  = typeToRoughMatchLookupTc ty'
+  | CastTy ty' _ <- ty
   = typeToRoughMatchLookupTc ty'
   | otherwise
   = case splitAppTys ty of


=====================================
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/GHC/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs
=====================================
The diff for this file was not included because it is too large.

=====================================
libraries/base/changelog.md
=====================================
@@ -4,6 +4,8 @@
   * Add `Data.List.!?` ([CLC proposal #110](https://github.com/haskell/core-libraries-committee/issues/110))
   * `maximumBy`/`minimumBy` are now marked as `INLINE` improving performance for unpackable
     types significantly.
+  * Refactor `generalCategory` to stop very large literal string being inlined to call-sites.
+      ([CLC proposal #130](https://github.com/haskell/core-libraries-committee/issues/130))
 
 ## 4.18.0.0 *TBA*
 
@@ -12,10 +14,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


=====================================
libraries/base/tools/ucd2haskell/exe/Parser/Text.hs
=====================================
@@ -205,7 +205,11 @@ genEnumBitmap funcName def as = unlines
                <> show (length as)
                <> " then "
                <> show (fromEnum def)
-               <> " else lookupIntN bitmap# n"
+               <> " else lookup_bitmap n"
+
+    , "{-# NOINLINE lookup_bitmap #-}"
+    , "lookup_bitmap :: Int -> Int"
+    , "lookup_bitmap n = lookupIntN bitmap# n"
     , "  where"
     , "    bitmap# = \"" <> enumMapToAddrLiteral as "\"#"
     ]


=====================================
testsuite/tests/typecheck/should_compile/T22985a.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985a where
+
+type Phase n = n
+
+addExpr :: Eq a => Phase a -> ()
+addExpr _ = ()


=====================================
testsuite/tests/typecheck/should_compile/T22985b.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985b where
+
+type Phase n = n
+
+addExpr :: Num a => Phase a -> a
+addExpr x = let t = asTypeOf x 0 in t


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -861,4 +861,5 @@ test('T20666b', normal, compile, [''])
 test('T22891', normal, compile, [''])
 test('T22912', normal, compile, [''])
 test('T22924', normal, compile, [''])
-
+test('T22985a', normal, compile, ['-O'])
+test('T22985b', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce95ad50babd6cad2ae230a6d3a058b646538370...dcd637ee5aa36ac59e6658ce7f7477a75ec7afd9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce95ad50babd6cad2ae230a6d3a058b646538370...dcd637ee5aa36ac59e6658ce7f7477a75ec7afd9
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/1512fcb5/attachment-0001.html>


More information about the ghc-commits mailing list