[Git][ghc/ghc][wip/T18580] 2 commits: Clean up TBDs in changelog

Ben Gamari gitlab at gitlab.haskell.org
Mon Aug 17 14:31:41 UTC 2020



Ben Gamari pushed to branch wip/T18580 at Glasgow Haskell Compiler / GHC


Commits:
f6c37b88 by Ben Gamari at 2020-08-17T10:31:32-04:00
Clean up TBDs in changelog

- - - - -
24d197ea by Ben Gamari at 2020-08-17T10:31:36-04:00
base: Fail if `timeout` is used when exceptions are masked

As pointed out in #18580, `timeout`'s implementation assumes that
exceptions will be handled. Document and assert this precondition.

Fixes #18580.

- - - - -


3 changed files:

- libraries/base/System/Timeout.hs
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md


Changes:

=====================================
libraries/base/System/Timeout.hs
=====================================
@@ -27,7 +27,8 @@ import Control.Concurrent
 import Control.Exception   (Exception(..), handleJust, bracket,
                             uninterruptibleMask_,
                             asyncExceptionToException,
-                            asyncExceptionFromException)
+                            asyncExceptionFromException,
+                            getMaskingState, MaskingState(..))
 import Data.Unique         (Unique, newUnique)
 
 -- An internal type that is thrown as a dynamic exception to
@@ -89,12 +90,16 @@ instance Exception Timeout where
 -- Note that 'timeout' cancels the computation by throwing it the 'Timeout'
 -- exception. Consequently blanket exception handlers (e.g. catching
 -- 'SomeException') within the computation will break the timeout behavior.
-timeout :: Int -> IO a -> IO (Maybe a)
+-- Moreover, 'timeout' cannot be used when in a context enclosed by
+-- by 'Control.Exception.uninterruptibleMask'.
+timeout :: HasCallStack => Int -> IO a -> IO (Maybe a)
 timeout n f
     | n <  0    = fmap Just f
     | n == 0    = return Nothing
 #if !defined(mingw32_HOST_OS)
     | rtsSupportsBoundThreads = do
+        checkNonUninterruptibleMask
+
         -- In the threaded RTS, we use the Timer Manager to delay the
         -- (fairly expensive) 'forkIO' call until the timeout has expired.
         --
@@ -125,6 +130,7 @@ timeout n f
                             (\_ -> fmap Just f))
 #endif
     | otherwise = do
+        checkNonUninterruptibleMask
         pid <- myThreadId
         ex  <- fmap Timeout newUnique
         handleJust (\e -> if e == ex then Just () else Nothing)
@@ -134,3 +140,9 @@ timeout n f
                             (uninterruptibleMask_ . killThread)
                             (\_ -> fmap Just f))
         -- #7719 explains why we need uninterruptibleMask_ above.
+  where
+    checkNonUninterruptibleMask :: HasCallStack => IO ()
+    checkNonUninterruptibleMask = do
+      maskingState <- getMaskingState
+      when (maskingState == Unmasked) $
+        error "System.Timeout.timeout called with exceptions uninterruptibly masked"


=====================================
libraries/base/changelog.md
=====================================
@@ -1,5 +1,11 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
+## 4.16.0.0 *TBA*
+
+  * `System.Timeout.timeout` now throws an error if called in a context where
+    exceptions have been masked since its implementation relies on exceptions to
+    interrupt its sub-computation (fixes #18580).
+
 ## 4.15.0.0 *TBA*
 
   * `openFile` now calls the `open` system call with an `interruptible` FFI
@@ -30,7 +36,7 @@
 
   * Add `Ix` instances for tuples of size 6 through 15
    
-## 4.14.0.0 *TBA*
+## 4.14.0.0 *Jan 2020
   * Bundled with GHC 8.10.1
 
   * Add a `TestEquality` instance for the `Compose` newtype.
@@ -322,7 +328,7 @@
     in constant space when applied to lists. (#10830)
 
   * `mkFunTy`, `mkAppTy`, and `mkTyConApp` from `Data.Typeable` no longer exist.
-    This functionality is superseded by the interfaces provided by
+    This functionality is superceded by the interfaces provided by
     `Type.Reflection`.
 
   * `mkTyCon3` is no longer exported by `Data.Typeable`. This function is


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -34,7 +34,9 @@
 
   * The argument to `TExpQ` can now be levity polymorphic.
 
-## 2.16.0.0 *TBA*
+## 2.16.0.0 *Jan 2020*
+
+  * Bundled with GHC 8.10.1
 
   * Add support for tuple sections. (#15843) The type signatures of `TupE` and
     `UnboxedTupE` have changed from `[Exp] -> Exp` to `[Maybe Exp] -> Exp`.
@@ -58,6 +60,8 @@
 
 ## 2.15.0.0 *May 2019*
 
+  * Bundled with GHC 8.8.1
+
   * In `Language.Haskell.TH.Syntax`, `DataInstD`, `NewTypeInstD`, `TySynEqn`,
     and `RuleP` now all have a `Maybe [TyVarBndr]` argument, which contains a
     list of quantified type variables if an explicit `forall` is present, and
@@ -80,6 +84,8 @@
 
 ## 2.14.0.0 *September 2018*
 
+  * Bundled with GHC 8.6.1
+
   * Introduce an `addForeignFilePath` function, as well as a corresponding
     `qAddForeignFile` class method to `Quasi`. Unlike `addForeignFile`, which
     takes the contents of the file as an argument, `addForeignFilePath` takes



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f07780443c659b979e73f4c704f11daa8f1bf62e...24d197eac9ee5fb593de1ef7a46ca1bb24362a42

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f07780443c659b979e73f4c704f11daa8f1bf62e...24d197eac9ee5fb593de1ef7a46ca1bb24362a42
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/20200817/0625a727/attachment-0001.html>


More information about the ghc-commits mailing list