Refer to 'mask' instead of 'block' in documentation of Control.Exception
[ghc-base.git] / Control / Exception.hs
index 5ef9b42..c573e3a 100644 (file)
@@ -53,8 +53,8 @@ module Control.Exception (
         System.ExitCode(), -- instance Exception
 #endif
 
-        BlockedOnDeadMVar(..),
-        BlockedIndefinitely(..),
+        BlockedIndefinitelyOnMVar(..),
+        BlockedIndefinitelyOnSTM(..),
         Deadlock(..),
         NoMethodError(..),
         PatternMatchFail(..),
@@ -73,9 +73,11 @@ module Control.Exception (
 
         -- * Catching Exceptions
 
-        -- |There are several functions for catching and examining
-        -- exceptions; all of them may only be used from within the
-        -- 'IO' monad.
+        -- $catching
+
+        -- ** Catching all exceptions
+
+        -- $catchall
 
         -- ** The @catch@ functions
         catch,
@@ -102,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
 
@@ -130,16 +143,12 @@ module Control.Exception (
         finally,
         onException,
 
-        -- * Catching all exceptions
-
-        -- $catchall
   ) where
 
 import Control.Exception.Base
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IOBase
 import Data.Maybe
 #else
 import Prelude hiding (catch)
@@ -181,6 +190,45 @@ catchesHandler handlers e = foldr tryHandler (throw e) handlers
                 Nothing -> res
 
 -- -----------------------------------------------------------------------------
+-- Catching exceptions
+
+{- $catching
+
+There are several functions for catching and examining
+exceptions; all of them may only be used from within the
+'IO' monad.
+
+Here's a rule of thumb for deciding which catch-style function to
+use:
+
+ * If you want to do some cleanup in the event that an exception
+   is raised, use 'finally', 'bracket' or 'onException'.
+
+ * To recover after an exception and do something else, the best
+   choice is to use one of the 'try' family.
+
+ * ... unless you are recovering from an asynchronous exception, in which
+   case use 'catch' or 'catchJust'.
+
+The difference between using 'try' and 'catch' for recovery is that in
+'catch' the handler is inside an implicit 'block' (see \"Asynchronous
+Exceptions\") which is important when catching asynchronous
+exceptions, but when catching other kinds of exception it is
+unnecessary.  Furthermore it is possible to accidentally stay inside
+the implicit 'block' by tail-calling rather than returning from the
+handler, which is why we recommend using 'try' rather than 'catch' for
+ordinary exception recovery.
+
+A typical use of 'tryJust' for recovery looks like this:
+
+>  do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME"
+>     case r of
+>       Left  e    -> ...
+>       Right home -> ...
+
+-}
+
+-- -----------------------------------------------------------------------------
 -- Asynchronous exceptions
 
 {- $async
@@ -205,34 +253,33 @@ 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.
 
 Note that 'try' and friends /do not/ have a similar default, because
-there is no exception handler in this case.  If you want to use 'try'
-in an asynchronous-exception-safe way, you will need to use
-'block'.
+there is no exception handler in this case.  Don't use 'try' for
+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'),
@@ -240,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
@@ -266,23 +312,22 @@ It is possible to catch all exceptions, by using the type 'SomeException':
 HOWEVER, this is normally not what you want to do!
 
 For example, suppose you want to read a file, but if it doesn't exist
-then continue as if it contained \"\". In the old exceptions library,
-the easy thing to do was just to catch all exceptions and return \"\" in
-the handler. However, this has all sorts of undesirable consequences.
-For example, if the user presses control-C at just the right moment then
-the 'UserInterrupt' exception will be caught, and the program will
-continue running under the belief that the file contains \"\".
-Similarly, if another thread tries to kill the thread reading the file
-then the 'ThreadKilled' exception will be ignored.
+then continue as if it contained \"\".  You might be tempted to just
+catch all exceptions and return \"\" in the handler. However, this has
+all sorts of undesirable consequences.  For example, if the user
+presses control-C at just the right moment then the 'UserInterrupt'
+exception will be caught, and the program will continue running under
+the belief that the file contains \"\".  Similarly, if another thread
+tries to kill the thread reading the file then the 'ThreadKilled'
+exception will be ignored.
 
 Instead, you should only catch exactly the exceptions that you really
 want. In this case, this would likely be more specific than even
 \"any IO exception\"; a permissions error would likely also want to be
 handled differently. Instead, you would probably want something like:
 
-> catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing)
->           (readFile f)
->           (\_ -> return "")
+> e <- tryJust (guard . isDoesNotExistError) (readFile f)
+> let str = either (const "") id e
 
 There are occassions when you really do need to catch any sort of
 exception. However, in most cases this is just so you can do some