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

Commits:

2 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -4,6 +4,8 @@
    4 4
       * Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337))
    
    5 5
     
    
    6 6
     ## 4.22.0.0 *TBA*
    
    7
    +  * Shipped with GHC 9.14.1
    
    8
    +  * The internal `GHC.Weak.Finalize.runFinalizerBatch` function has been deprecated ([CLC proposal #342](https://github.com/haskell/core-libraries-committee/issues/342))
    
    7 9
       * Define `displayException` of `SomeAsyncException` to unwrap the exception.
    
    8 10
           ([CLC proposal #309](https://github.com/haskell/core-libraries-committee/issues/309))
    
    9 11
       * Restrict `Data.List.NonEmpty.unzip` to `NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)`. ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
    

  • libraries/base/src/GHC/Weak/Finalize.hs
    1
    +{-# LANGUAGE MagicHash #-}
    
    1 2
     module GHC.Weak.Finalize
    
    2 3
         ( -- * Handling exceptions
    
    3 4
           -- | When an exception is thrown by a finalizer called by the
    
    ... ... @@ -8,7 +9,30 @@ module GHC.Weak.Finalize
    8 9
         , getFinalizerExceptionHandler
    
    9 10
         , printToHandleFinalizerExceptionHandler
    
    10 11
           -- * Internal
    
    11
    -    , runFinalizerBatch
    
    12
    +    , GHC.Weak.Finalize.runFinalizerBatch
    
    12 13
         ) where
    
    13 14
     
    
    14 15
     import GHC.Internal.Weak.Finalize
    
    16
    +
    
    17
    +-- These imports can be removed once runFinalizerBatch is removed,
    
    18
    +-- as can MagicHash above.
    
    19
    +import GHC.Internal.Base (Int, Array#, IO, State#, RealWorld)
    
    20
    +
    
    21
    +
    
    22
    +{-# DEPRECATED runFinalizerBatch
    
    23
    +    "This function is internal to GHC. It will not be exported in future." #-}
    
    24
    +-- | Run a batch of finalizers from the garbage collector. Given an
    
    25
    +-- array of finalizers and the length of the array, just call each one
    
    26
    +-- in turn.
    
    27
    +--
    
    28
    +-- This is an internal detail of the GHC RTS weak pointer finaliser
    
    29
    +-- mechanism. It should no longer be exported from base. There is no
    
    30
    +-- good reason to use it. It will be removed in the next major version
    
    31
    +-- of base (4.23.*).
    
    32
    +--
    
    33
    +-- See <https://github.com/haskell/core-libraries-committee/issues/342>
    
    34
    +--
    
    35
    +runFinalizerBatch :: Int
    
    36
    +                  -> Array# (State# RealWorld -> State# RealWorld)
    
    37
    +                  -> IO ()
    
    38
    +runFinalizerBatch = GHC.Internal.Weak.Finalize.runFinalizerBatch