Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / GHC / IO / Exception.hs
index 232ed83..4134fca 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -fno-implicit-prelude -funbox-strict-fields #-}
+{-# LANGUAGE NoImplicitPrelude, DeriveDataTypeable, MagicHash #-}
+{-# OPTIONS_GHC -funbox-strict-fields #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
@@ -15,8 +16,8 @@
 -----------------------------------------------------------------------------
 
 module GHC.IO.Exception (
-  BlockedOnDeadMVar(..),   blockedOnDeadMVar,
-  BlockedIndefinitely(..), blockedIndefinitely,
+  BlockedIndefinitelyOnMVar(..), blockedIndefinitelyOnMVar,
+  BlockedIndefinitelyOnSTM(..), blockedIndefinitelyOnSTM,
   Deadlock(..),
   AssertionFailed(..),
   AsyncException(..), stackOverflow, heapOverflow,
@@ -51,31 +52,31 @@ import Data.Typeable     ( Typeable )
 
 -- |The thread is blocked on an @MVar@, but there are no other references
 -- to the @MVar@ so it can't ever continue.
-data BlockedOnDeadMVar = BlockedOnDeadMVar
+data BlockedIndefinitelyOnMVar = BlockedIndefinitelyOnMVar
     deriving Typeable
 
-instance Exception BlockedOnDeadMVar
+instance Exception BlockedIndefinitelyOnMVar
 
-instance Show BlockedOnDeadMVar where
-    showsPrec _ BlockedOnDeadMVar = showString "thread blocked indefinitely"
+instance Show BlockedIndefinitelyOnMVar where
+    showsPrec _ BlockedIndefinitelyOnMVar = showString "thread blocked indefinitely in an MVar operation"
 
-blockedOnDeadMVar :: SomeException -- for the RTS
-blockedOnDeadMVar = toException BlockedOnDeadMVar
+blockedIndefinitelyOnMVar :: SomeException -- for the RTS
+blockedIndefinitelyOnMVar = toException BlockedIndefinitelyOnMVar
 
 -----
 
--- |The thread is awiting to retry an STM transaction, but there are no
+-- |The thread is waiting to retry an STM transaction, but there are no
 -- other references to any @TVar@s involved, so it can't ever continue.
-data BlockedIndefinitely = BlockedIndefinitely
+data BlockedIndefinitelyOnSTM = BlockedIndefinitelyOnSTM
     deriving Typeable
 
-instance Exception BlockedIndefinitely
+instance Exception BlockedIndefinitelyOnSTM
 
-instance Show BlockedIndefinitely where
-    showsPrec _ BlockedIndefinitely = showString "thread blocked indefinitely"
+instance Show BlockedIndefinitelyOnSTM where
+    showsPrec _ BlockedIndefinitelyOnSTM = showString "thread blocked indefinitely in an STM transaction"
 
-blockedIndefinitely :: SomeException -- for the RTS
-blockedIndefinitely = toException BlockedIndefinitely
+blockedIndefinitelyOnSTM :: SomeException -- for the RTS
+blockedIndefinitelyOnSTM = toException BlockedIndefinitelyOnSTM
 
 -----
 
@@ -91,8 +92,7 @@ instance Show Deadlock where
 
 -----
 
--- |There are no runnable threads, so the program is deadlocked.
--- The @Deadlock@ exception is raised in the main thread only.
+-- |'assert' was applied to 'False'.
 data AssertionFailed = AssertionFailed String
     deriving Typeable
 
@@ -170,6 +170,7 @@ instance Show ArrayException where
 -- We need it here because it is used in ExitException in the
 -- Exception datatype (above).
 
+-- | Defines the exit codes that a program can return.
 data ExitCode
   = ExitSuccess -- ^ indicates successful termination;
   | ExitFailure Int
@@ -194,7 +195,7 @@ ioError         =  ioException
 -- | The Haskell 98 type for exceptions in the 'IO' monad.
 -- Any I\/O operation may raise an 'IOError' instead of returning a result.
 -- For a more general type of exception, including also those that arise
--- in pure code, see 'Control.Exception.Exception'.
+-- in pure code, see "Control.Exception.Exception".
 --
 -- In Haskell 98, this is an opaque type.
 type IOError = IOException