Integrated new I/O manager
[ghc-base.git] / Control / Exception.hs
index e8032b7..d5d0e4c 100644 (file)
@@ -1,13 +1,11 @@
 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
 
-#include "Typeable.h"
-
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Exception
 -- Copyright   :  (c) The University of Glasgow 2001
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (extended exceptions)
 --  * /Asynchronous exceptions in Haskell/, by Simon Marlow, Simon Peyton
 --    Jones, Andy Moran and John Reppy, in /PLDI'01/.
 --
+--  * /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
+--    by Simon Marlow, in /Haskell '06/.
+--
 -----------------------------------------------------------------------------
 
 module Control.Exception (
 
         -- * The Exception type
+#ifdef __HUGS__
+        SomeException,
+#else
         SomeException(..),
-        Exception(..),          -- instance Eq, Ord, Show, Typeable
-        IOException,            -- instance Eq, Ord, Show, Typeable
-        ArithException(..),     -- instance Eq, Ord, Show, Typeable
-        ArrayException(..),     -- instance Eq, Ord, Show, Typeable
+#endif
+        Exception(..),          -- class
+        IOException,            -- instance Eq, Ord, Show, Typeable, Exception
+        ArithException(..),     -- instance Eq, Ord, Show, Typeable, Exception
+        ArrayException(..),     -- instance Eq, Ord, Show, Typeable, Exception
         AssertionFailed(..),
-        AsyncException(..),     -- instance Eq, Ord, Show, Typeable
-        NonTermination(..), nonTermination,
-        BlockedOnDeadMVar(..),
-        BlockedIndefinitely(..),
-        NestedAtomically(..), nestedAtomically,
+        AsyncException(..),     -- instance Eq, Ord, Show, Typeable, Exception
+
+#if __GLASGOW_HASKELL__ || __HUGS__
+        NonTermination(..),
+        NestedAtomically(..),
+#endif
+#ifdef __NHC__
+        System.ExitCode(), -- instance Exception
+#endif
+
+        BlockedIndefinitelyOnMVar(..),
+        BlockedIndefinitelyOnSTM(..),
         Deadlock(..),
         NoMethodError(..),
         PatternMatchFail(..),
@@ -52,38 +64,39 @@ module Control.Exception (
         ErrorCall(..),
 
         -- * Throwing exceptions
-        throwIO,        -- :: Exception -> IO a
-        throw,          -- :: Exception -> a
-        ioError,        -- :: IOError -> IO a
+        throw,
+        throwIO,
+        ioError,
 #ifdef __GLASGOW_HASKELL__
-        throwTo,        -- :: ThreadId -> Exception -> a
+        throwTo,
 #endif
 
         -- * 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,     -- :: IO a -> (Exception -> IO a) -> IO a
+        catch,
         catches, Handler(..),
-        catchJust, -- :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
+        catchJust,
 
         -- ** The @handle@ functions
-        handle,    -- :: (Exception -> IO a) -> IO a -> IO a
-        handleJust,-- :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
+        handle,
+        handleJust,
 
         -- ** The @try@ functions
-        try,       -- :: IO a -> IO (Either Exception a)
-        tryJust,   -- :: (Exception -> Maybe b) -> a    -> IO (Either b a)
-        onException,
+        try,
+        tryJust,
 
         -- ** The @evaluate@ function
-        evaluate,  -- :: a -> IO a
+        evaluate,
 
         -- ** The @mapException@ function
-        mapException,           -- :: (Exception -> Exception) -> a -> a
+        mapException,
 
         -- * Asynchronous Exceptions
 
@@ -91,12 +104,23 @@ 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.
 
-        block,          -- :: IO a -> IO a
-        unblock,        -- :: IO a -> IO a
-        blocked,        -- :: IO Bool
+        mask,
+#ifndef __NHC__
+        mask_,
+        uninterruptibleMask,
+        uninterruptibleMask_,
+        MaskingState(..),
+        getMaskingState,
+#endif
+
+        -- ** (deprecated) Asynchronous exception control
+
+        block,
+        unblock,
+        blocked,
 
         -- *** Applying @block@ to an exception handler
 
@@ -108,145 +132,53 @@ module Control.Exception (
 
         -- * Assertions
 
-        assert,         -- :: Bool -> a -> a
+        assert,
 
         -- * Utilities
 
-        bracket,        -- :: IO a -> (a -> IO b) -> (a -> IO c) -> IO ()
-        bracket_,       -- :: IO a -> IO b -> IO c -> IO ()
+        bracket,
+        bracket_,
         bracketOnError,
 
-        finally,        -- :: IO a -> IO b -> IO a
+        finally,
+        onException,
 
-        recSelError, recConError, irrefutPatError, runtimeError,
-        nonExhaustiveGuardsError, patError, noMethodBindingError,
-        assertError,
   ) where
 
+import Control.Exception.Base
+
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IOBase
-import GHC.List
-import GHC.Show
-import GHC.IOBase as ExceptionBase
-import GHC.Exception hiding ( Exception )
-import GHC.Conc         ( ThreadId(ThreadId) )
-#endif
-
-#ifdef __HUGS__
-import Hugs.Exception   as ExceptionBase
-#endif
-
-import Data.Dynamic
-import Data.Either
 import Data.Maybe
+#else
+import Prelude hiding (catch)
+#endif
 
 #ifdef __NHC__
-import qualified System.IO.Error as H'98 (catch)
-import System.IO.Error (ioError)
-import IO              (bracket)
-import DIOError         -- defn of IOError type
-import System          (ExitCode())
-
--- minimum needed for nhc98 to pretend it has Exceptions
-data Exception   = IOException    IOException
-                 | ArithException ArithException
-                 | ArrayException ArrayException
-                 | AsyncException AsyncException
-                 | ExitException  ExitCode
-                 deriving Show
-type IOException = IOError
-data ArithException
-data ArrayException
-data AsyncException
-instance Show ArithException
-instance Show ArrayException
-instance Show AsyncException
-
-catch    :: IO a -> (Exception -> IO a) -> IO a
-a `catch` b = a `H'98.catch` (b . IOException)
-
-throwIO  :: Exception -> IO a
-throwIO (IOException e) = ioError e
-throwIO _               = ioError (UserError "Control.Exception.throwIO"
-                                             "unknown exception")
-throw    :: Exception -> a
-throw     = unsafePerformIO . throwIO
-
-evaluate :: a -> IO a
-evaluate x = x `seq` return x
-
-assert :: Bool -> a -> a
-assert True  x = x
-assert False _ = throw (IOException (UserError "" "Assertion failed"))
+import System (ExitCode())
 #endif
 
-#ifndef __GLASGOW_HASKELL__
--- Dummy definitions for implementations lacking asynchonous exceptions
+-- | You need this when using 'catches'.
+data Handler a = forall e . Exception e => Handler (e -> IO a)
 
-block   :: IO a -> IO a
-block    = id
-unblock :: IO a -> IO a
-unblock  = id
-blocked :: IO Bool
-blocked  = return False
-#endif
+{- |
+Sometimes you want to catch two different sorts of exception. You could
+do something like
 
------------------------------------------------------------------------------
--- Catching exceptions
+> f = expr `catch` \ (ex :: ArithException) -> handleArith ex
+>          `catch` \ (ex :: IOException)    -> handleIO    ex
 
--- |This is the simplest of the exception-catching functions.  It
--- takes a single argument, runs it, and if an exception is raised
--- the \"handler\" is executed, with the value of the exception passed as an
--- argument.  Otherwise, the result is returned as normal.  For example:
---
--- >   catch (openFile f ReadMode) 
--- >       (\e -> hPutStr stderr ("Couldn't open "++f++": " ++ show e))
---
--- For catching exceptions in pure (non-'IO') expressions, see the
--- function 'evaluate'.
---
--- Note that due to Haskell\'s unspecified evaluation order, an
--- expression may return one of several possible exceptions: consider
--- the expression @error \"urk\" + 1 \`div\` 0@.  Does
--- 'catch' execute the handler passing
--- @ErrorCall \"urk\"@, or @ArithError DivideByZero@?
---
--- The answer is \"either\": 'catch' makes a
--- non-deterministic choice about which exception to catch.  If you
--- call it again, you might get a different exception back.  This is
--- ok, because 'catch' is an 'IO' computation.
---
--- Note that 'catch' catches all types of exceptions, and is generally
--- used for \"cleaning up\" before passing on the exception using
--- 'throwIO'.  It is not good practice to discard the exception and
--- continue, without first checking the type of the exception (it
--- might be a 'ThreadKilled', for example).  In this case it is usually better
--- to use 'catchJust' and select the kinds of exceptions to catch.
---
--- Also note that the "Prelude" also exports a function called
--- 'Prelude.catch' with a similar type to 'Control.Exception.catch',
--- except that the "Prelude" version only catches the IO and user
--- families of exceptions (as required by Haskell 98).  
---
--- We recommend either hiding the "Prelude" version of 'Prelude.catch'
--- when importing "Control.Exception": 
---
--- > import Prelude hiding (catch)
---
--- or importing "Control.Exception" qualified, to avoid name-clashes:
---
--- > import qualified Control.Exception as C
---
--- and then using @C.catch@
---
-#ifndef __NHC__
-catch   :: Exception e
-        => IO a         -- ^ The computation to run
-        -> (e -> IO a)  -- ^ Handler to invoke if an exception is raised
-        -> IO a
-catch = ExceptionBase.catchException
+However, there are a couple of problems with this approach. The first is
+that having two exception handlers is inefficient. However, the more
+serious issue is that the second exception handler will catch exceptions
+in the first, e.g. in the example above, if @handleArith@ throws an
+@IOException@ then the second exception handler will catch it.
 
+Instead, we provide a function 'catches', which would be used thus:
+
+> f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
+>                     Handler (\ (ex :: IOException)    -> handleIO    ex)]
+-}
 catches :: IO a -> [Handler a] -> IO a
 catches io handlers = io `catch` catchesHandler handlers
 
@@ -257,158 +189,44 @@ catchesHandler handlers e = foldr tryHandler (throw e) handlers
                 Just e' -> handler e'
                 Nothing -> res
 
-data Handler a = forall e . Exception e => Handler (e -> IO a)
-#endif
--- | The function 'catchJust' is like 'catch', but it takes an extra
--- argument which is an /exception predicate/, a function which
--- selects which type of exceptions we\'re interested in.
---
--- >   result <- catchJust errorCalls thing_to_try handler
---
--- Any other exceptions which are not matched by the predicate
--- are re-raised, and may be caught by an enclosing
--- 'catch' or 'catchJust'.
-catchJust
-        :: Exception e
-        => (e -> Maybe b)         -- ^ Predicate to select exceptions
-        -> IO a                   -- ^ Computation to run
-        -> (b -> IO a)            -- ^ Handler
-        -> IO a
-catchJust p a handler = catch a handler'
-  where handler' e = case p e of 
-                        Nothing -> throw e
-                        Just b  -> handler b
-
--- | A version of 'catch' with the arguments swapped around; useful in
--- situations where the code for the handler is shorter.  For example:
---
--- >   do handle (\e -> exitWith (ExitFailure 1)) $
--- >      ...
-handle     :: Exception e => (e -> IO a) -> IO a -> IO a
-handle     =  flip catch
+-- -----------------------------------------------------------------------------
+-- Catching exceptions
 
--- | A version of 'catchJust' with the arguments swapped around (see
--- 'handle').
-handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
-handleJust p =  flip (catchJust p)
+{- $catching
 
------------------------------------------------------------------------------
--- 'mapException'
+There are several functions for catching and examining
+exceptions; all of them may only be used from within the
+'IO' monad.
 
--- | This function maps one exception into another as proposed in the
--- paper \"A semantics for imprecise exceptions\".
+Here's a rule of thumb for deciding which catch-style function to
+use:
 
--- Notice that the usage of 'unsafePerformIO' is safe here.
+ * If you want to do some cleanup in the event that an exception
+   is raised, use 'finally', 'bracket' or 'onException'.
 
-mapException :: Exception e => (e -> e) -> a -> a
-mapException f v = unsafePerformIO (catch (evaluate v)
-                                          (\x -> throw (f x)))
+ * To recover after an exception and do something else, the best
+   choice is to use one of the 'try' family.
 
------------------------------------------------------------------------------
--- 'try' and variations.
+ * ... unless you are recovering from an asynchronous exception, in which
+   case use 'catch' or 'catchJust'.
 
--- | Similar to 'catch', but returns an 'Either' result which is
--- @('Right' a)@ if no exception was raised, or @('Left' e)@ if an
--- exception was raised and its value is @e@.
---
--- >  try a = catch (Right `liftM` a) (return . Left)
---
--- Note: as with 'catch', it is only polite to use this variant if you intend
--- to re-throw the exception after performing whatever cleanup is needed.
--- Otherwise, 'tryJust' is generally considered to be better.
---
--- Also note that "System.IO.Error" also exports a function called
--- 'System.IO.Error.try' with a similar type to 'Control.Exception.try',
--- except that it catches only the IO and user families of exceptions
--- (as required by the Haskell 98 @IO@ module).
-
-try :: Exception e => IO a -> IO (Either e a)
-try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e))
-
--- | A variant of 'try' that takes an exception predicate to select
--- which exceptions are caught (c.f. 'catchJust').  If the exception
--- does not match the predicate, it is re-thrown.
-tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a)
-tryJust p a = do
-  r <- try a
-  case r of
-        Right v -> return (Right v)
-        Left  e -> case p e of
-                        Nothing -> throw e
-                        Just b  -> return (Left b)
-
-onException :: IO a -> IO () -> IO a
-onException io what = io `catch` \e -> do what
-                                          throw (e :: SomeException)
+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.
 
------------------------------------------------------------------------------
--- Some Useful Functions
-
--- | When you want to acquire a resource, do some work with it, and
--- then release the resource, it is a good idea to use 'bracket',
--- because 'bracket' will install the necessary exception handler to
--- release the resource in the event that an exception is raised
--- during the computation.  If an exception is raised, then 'bracket' will 
--- re-raise the exception (after performing the release).
---
--- A common example is opening a file:
---
--- > bracket
--- >   (openFile "filename" ReadMode)
--- >   (hClose)
--- >   (\handle -> do { ... })
---
--- The arguments to 'bracket' are in this order so that we can partially apply 
--- it, e.g.:
---
--- > withFile name mode = bracket (openFile name mode) hClose
---
-#ifndef __NHC__
-bracket 
-        :: IO a         -- ^ computation to run first (\"acquire resource\")
-        -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
-        -> (a -> IO c)  -- ^ computation to run in-between
-        -> IO c         -- returns the value from the in-between computation
-bracket before after thing =
-  block (do
-    a <- before 
-    r <- unblock (thing a) `onException` after a
-    after a
-    return r
- )
-#endif
+A typical use of 'tryJust' for recovery looks like this:
 
--- | A specialised variant of 'bracket' with just a computation to run
--- afterward.
--- 
-finally :: IO a         -- ^ computation to run first
-        -> IO b         -- ^ computation to run afterward (even if an exception 
-                        -- was raised)
-        -> IO a         -- returns the value from the first computation
-a `finally` sequel =
-  block (do
-    r <- unblock a `onException` sequel
-    sequel
-    return r
-  )
-
--- | A variant of 'bracket' where the return value from the first computation
--- is not required.
-bracket_ :: IO a -> IO b -> IO c -> IO c
-bracket_ before after thing = bracket before (const after) (const thing)
-
--- | Like bracket, but only performs the final action if there was an 
--- exception raised by the in-between computation.
-bracketOnError
-        :: IO a         -- ^ computation to run first (\"acquire resource\")
-        -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
-        -> (a -> IO c)  -- ^ computation to run in-between
-        -> IO c         -- returns the value from the in-between computation
-bracketOnError before after thing =
-  block (do
-    a <- before 
-    unblock (thing a) `onException` after a
- )
+>  do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME"
+>     case r of
+>       Left  e    -> ...
+>       Right home -> ...
+
+-}
 
 -- -----------------------------------------------------------------------------
 -- Asynchronous exceptions
@@ -435,7 +253,7 @@ 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
@@ -445,22 +263,21 @@ 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)
->      )
+>      block $ \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
 which may itself block is defined as interruptible; this includes
@@ -470,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
@@ -487,150 +303,46 @@ Similar arguments apply for other interruptible operations like
 'System.IO.openFile'.
 -}
 
-#if !(__GLASGOW_HASKELL__ || __NHC__)
-assert :: Bool -> a -> a
-assert True x = x
-assert False _ = throw (AssertionFailed "")
-#endif
-
-recSelError, recConError, irrefutPatError, runtimeError,
-             nonExhaustiveGuardsError, patError, noMethodBindingError
-        :: Addr# -> a   -- All take a UTF8-encoded C string
-
-recSelError              s = throw (RecSelError (unpackCStringUtf8# s)) -- No location info unfortunately
-runtimeError             s = error (unpackCStringUtf8# s)               -- No location info unfortunately
-
-nonExhaustiveGuardsError s = throw (PatternMatchFail (untangle s "Non-exhaustive guards in"))
-irrefutPatError          s = throw (PatternMatchFail (untangle s "Irrefutable pattern failed for pattern"))
-recConError              s = throw (RecConError      (untangle s "Missing field in record construction"))
-noMethodBindingError     s = throw (NoMethodError    (untangle s "No instance nor default method for class operation"))
-patError                 s = throw (PatternMatchFail (untangle s "Non-exhaustive patterns in"))
-
------
-
-data PatternMatchFail = PatternMatchFail String
-INSTANCE_TYPEABLE0(PatternMatchFail,patternMatchFailTc,"PatternMatchFail")
-
-instance Exception PatternMatchFail
-
-instance Show PatternMatchFail where
-    showsPrec _ (PatternMatchFail err) = showString err
-
------
-
-data RecSelError = RecSelError String
-INSTANCE_TYPEABLE0(RecSelError,recSelErrorTc,"RecSelError")
-
-instance Exception RecSelError
-
-instance Show RecSelError where
-    showsPrec _ (RecSelError err) = showString err
-
------
-
-data RecConError = RecConError String
-INSTANCE_TYPEABLE0(RecConError,recConErrorTc,"RecConError")
-
-instance Exception RecConError
-
-instance Show RecConError where
-    showsPrec _ (RecConError err) = showString err
-
------
-
-data RecUpdError = RecUpdError String
-INSTANCE_TYPEABLE0(RecUpdError,recUpdErrorTc,"RecUpdError")
-
-instance Exception RecUpdError
-
-instance Show RecUpdError where
-    showsPrec _ (RecUpdError err) = showString err
-
------
-
-data NoMethodError = NoMethodError String
-INSTANCE_TYPEABLE0(NoMethodError,noMethodErrorTc,"NoMethodError")
-
-instance Exception NoMethodError
-
-instance Show NoMethodError where
-    showsPrec _ (NoMethodError err) = showString err
-
------
-
-data AssertionFailed = AssertionFailed String
-INSTANCE_TYPEABLE0(AssertionFailed,assertionFailedTc,"AssertionFailed")
-
-instance Exception AssertionFailed
-
-instance Show AssertionFailed where
-    showsPrec _ (AssertionFailed err) = showString err
-
------
-
-data NonTermination = NonTermination
-INSTANCE_TYPEABLE0(NonTermination,nonTerminationTc,"NonTermination")
-
-instance Exception NonTermination
-
-instance Show NonTermination where
-    showsPrec _ NonTermination = showString "<<loop>>"
-
--- GHC's RTS calls this
-nonTermination :: SomeException
-nonTermination = toException NonTermination
-
------
-
-data NestedAtomically = NestedAtomically
-INSTANCE_TYPEABLE0(NestedAtomically,nestedAtomicallyTc,"NestedAtomically")
-
-instance Exception NestedAtomically
-
-instance Show NestedAtomically where
-    showsPrec _ NestedAtomically = showString "Control.Concurrent.STM.atomically was nested"
-
--- GHC's RTS calls this
-nestedAtomically :: SomeException
-nestedAtomically = toException NestedAtomically
-
------
-
-instance Exception Dynamic
-
------
-
-assertError :: Addr# -> Bool -> a -> a
-assertError str pred v
-  | pred      = v
-  | otherwise = throw (AssertionFailed (untangle str "Assertion failed"))
-
-{-
-(untangle coded message) expects "coded" to be of the form
-        "location|details"
-It prints
-        location message details
+{- $catchall
+
+It is possible to catch all exceptions, by using the type 'SomeException':
+
+> catch f (\e -> ... (e :: 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 \"\".  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:
+
+> 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
+cleaning up; you aren't actually interested in the exception itself.
+For example, if you open a file then you want to close it again,
+whether processing the file executes normally or throws an exception.
+However, in these cases you can use functions like 'bracket', 'finally'
+and 'onException', which never actually pass you the exception, but
+just call the cleanup functions at the appropriate points.
+
+But sometimes you really do need to catch any exception, and actually
+see what the exception is. One example is at the very top-level of a
+program, you may wish to catch any exception, print it to a logfile or
+the screen, and then exit gracefully. For these cases, you can use
+'catch' (or one of the other exception-catching functions) with the
+'SomeException' type.
 -}
-untangle :: Addr# -> String -> String
-untangle coded message
-  =  location
-  ++ ": " 
-  ++ message
-  ++ details
-  ++ "\n"
-  where
-    coded_str = unpackCStringUtf8# coded
-
-    (location, details)
-      = case (span not_bar coded_str) of { (loc, rest) ->
-        case rest of
-          ('|':det) -> (loc, ' ' : det)
-          _         -> (loc, "")
-        }
-    not_bar c = c /= '|'
-
--- XXX From GHC.Conc
-throwTo :: Exception e => ThreadId -> e -> IO ()
-throwTo (ThreadId id) ex = IO $ \ s ->
-   case (killThread# id (toException ex) s) of s1 -> (# s1, () #)