Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Control / Exception.hs
index 9e7a4c9..03f6886 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, ExistentialQuantification #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -53,8 +53,8 @@ module Control.Exception (
         System.ExitCode(), -- instance Exception
 #endif
 
-        BlockedOnDeadMVar(..),
-        BlockedIndefinitely(..),
+        BlockedIndefinitelyOnMVar(..),
+        BlockedIndefinitelyOnSTM(..),
         Deadlock(..),
         NoMethodError(..),
         PatternMatchFail(..),
@@ -104,14 +104,25 @@ module Control.Exception (
 
         -- ** Asynchronous exception control
 
-        -- |The following two functions allow a thread to control delivery of
+        -- |The following functions allow a thread to control delivery of
         -- asynchronous exceptions during a critical region.
 
+        mask,
+#ifndef __NHC__
+        mask_,
+        uninterruptibleMask,
+        uninterruptibleMask_,
+        MaskingState(..),
+        getMaskingState,
+#endif
+
+        -- ** (deprecated) Asynchronous exception control
+
         block,
         unblock,
         blocked,
 
-        -- *** Applying @block@ to an exception handler
+        -- *** Applying @mask@ to an exception handler
 
         -- $block_handler
 
@@ -138,7 +149,6 @@ import Control.Exception.Base
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IOBase
 import Data.Maybe
 #else
 import Prelude hiding (catch)
@@ -233,7 +243,7 @@ The primary source of asynchronous exceptions, however, is
 
 >  throwTo :: ThreadId -> Exception -> IO ()
 
-'throwTo' (also 'throwDynTo' and 'Control.Concurrent.killThread') allows one
+'throwTo' (also 'Control.Concurrent.killThread') allows one
 running thread to raise an arbitrary exception in another thread.  The
 exception is therefore asynchronous with respect to the target thread,
 which could be doing anything at the time it receives the exception.
@@ -243,23 +253,22 @@ easy to introduce race conditions by the over zealous use of
 -}
 
 {- $block_handler
-There\'s an implied 'block' around every exception handler in a call
+There\'s an implied 'mask' around every exception handler in a call
 to one of the 'catch' family of functions.  This is because that is
 what you want most of the time - it eliminates a common race condition
 in starting an exception handler, because there may be no exception
 handler on the stack to handle another exception if one arrives
-immediately.  If asynchronous exceptions are blocked on entering the
+immediately.  If asynchronous exceptions are masked on entering the
 handler, though, we have time to install a new exception handler
 before being interrupted.  If this weren\'t the default, one would have
 to write something like
 
->      block (
->           catch (unblock (...))
->                      (\e -> handler)
->      )
+>      mask $ \restore ->
+>           catch (restore (...))
+>                 (\e -> handler)
 
 If you need to unblock asynchronous exceptions again in the exception
-handler, just use 'unblock' as normal.
+handler, 'restore' can be used there too.
 
 Note that 'try' and friends /do not/ have a similar default, because
 there is no exception handler in this case.  Don't use 'try' for
@@ -268,8 +277,9 @@ recovering from an asynchronous exception.
 
 {- $interruptible
 
+ #interruptible#
 Some operations are /interruptible/, which means that they can receive
-asynchronous exceptions even in the scope of a 'block'.  Any function
+asynchronous exceptions even in the scope of a 'mask'.  Any function
 which may itself block is defined as interruptible; this includes
 'Control.Concurrent.MVar.takeMVar'
 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
@@ -277,11 +287,10 @@ and most operations which perform
 some I\/O with the outside world.  The reason for having
 interruptible operations is so that we can write things like
 
->      block (
+>      mask $ \restore -> do
 >         a <- takeMVar m
->         catch (unblock (...))
+>         catch (restore (...))
 >               (\e -> ...)
->      )
 
 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
 then this particular
@@ -292,6 +301,49 @@ safe in the knowledge that the thread can receive exceptions right up
 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
 Similar arguments apply for other interruptible operations like
 'System.IO.openFile'.
+
+It is useful to think of 'mask' not as a way to completely prevent
+asynchronous exceptions, but as a filter that allows them to be raised
+only at certain places.  The main difficulty with asynchronous
+exceptions is that they normally can occur anywhere, but within a
+'mask' an asynchronous exception is only raised by operations that are
+interruptible (or call other interruptible operations).  In many cases
+these operations may themselves raise exceptions, such as I\/O errors,
+so the caller should be prepared to handle exceptions arising from the
+operation anyway.
+
+Sometimes it is too onerous to handle exceptions in the middle of a
+critical piece of stateful code.  There are three ways to handle this
+kind of situation:
+
+ * Use STM.  Since a transaction is always either completely executed
+   or not at all, transactions are a good way to maintain invariants
+   over state in the presence of asynchronous (and indeed synchronous)
+   exceptions.
+
+ * Use 'mask', and avoid interruptible operations.  In order to do
+   this, we have to know which operations are interruptible.  It is
+   impossible to know for any given library function whether it might
+   invoke an interruptible operation internally; so instead we give a
+   list of guaranteed-not-to-be-interruptible operations below.
+
+ * Use 'uninterruptibleMask'.  This is generally not recommended,
+   unless you can guarantee that any interruptible operations invoked
+   during the scope of 'uninterruptibleMask' can only ever block for
+   a short time.  Otherwise, 'uninterruptibleMask' is a good way to
+   make your program deadlock and be unresponsive to user interrupts.
+
+The following operations are guaranteed not to be interruptible:
+
+ * operations on 'IORef' from "Data.IORef"
+ * STM transactions that do not use 'retry'
+ * everything from the @Foreign@ modules
+ * everything from @Control.Exception@
+ * @tryTakeMVar@, @tryPutMVar@, @isEmptyMVar@
+ * @takeMVar@ if the @MVar@ is definitely full, and conversely @putMVar@ if the @MVar@ is definitely empty
+ * @newEmptyMVar@, @newMVar@
+ * @forkIO@, @forkIOUnmasked@, @myThreadId@
+
 -}
 
 {- $catchall