Remove unused foreign imports of __encodeFloat/Double
[ghc-base.git] / GHC / IOBase.lhs
index 9b4b0be..0a19d80 100644 (file)
@@ -27,7 +27,8 @@ module GHC.IOBase(
 
         -- References
     IORef(..), newIORef, readIORef, writeIORef, 
-    IOArray(..), newIOArray, readIOArray, writeIOArray, unsafeReadIOArray, unsafeWriteIOArray,
+    IOArray(..), newIOArray, readIOArray, writeIOArray, unsafeReadIOArray, 
+    unsafeWriteIOArray, boundsIOArray,
     MVar(..),
 
         -- Handles, file descriptors,
@@ -47,7 +48,8 @@ module GHC.IOBase(
     throwIO, block, unblock, blocked, catchAny, catchException,
     evaluate,
     ErrorCall(..), AssertionFailed(..), assertError, untangle,
-    BlockedOnDeadMVar(..), BlockedIndefinitely(..), Deadlock(..)
+    BlockedOnDeadMVar(..), BlockedIndefinitely(..), Deadlock(..),
+    blockedOnDeadMVar, blockedIndefinitely
   ) where
 
 import GHC.ST
@@ -65,7 +67,6 @@ import GHC.Exception
 
 #ifndef __HADDOCK__
 import {-# SOURCE #-} Data.Typeable     ( Typeable )
-import {-# SOURCE #-} Data.Dynamic      ( Dynamic )
 #endif
 
 -- ---------------------------------------------------------------------------
@@ -606,6 +607,9 @@ readIOArray (IOArray marr) i = stToIO (readSTArray marr i)
 writeIOArray :: Ix i => IOArray i e -> i -> e -> IO ()
 writeIOArray (IOArray marr) i e = stToIO (writeSTArray marr i e)
 
+{-# INLINE boundsIOArray #-}
+boundsIOArray :: IOArray i e -> (i,i)  
+boundsIOArray (IOArray marr) = boundsSTArray marr
 
 -- ---------------------------------------------------------------------------
 -- Show instance for Handles
@@ -634,6 +638,8 @@ showHandle file = showString "{handle: " . showString file . showString "}"
 -- ------------------------------------------------------------------------
 -- Exception datatypes and operations
 
+-- |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
     deriving Typeable
 
@@ -642,8 +648,13 @@ instance Exception BlockedOnDeadMVar
 instance Show BlockedOnDeadMVar where
     showsPrec _ BlockedOnDeadMVar = showString "thread blocked indefinitely"
 
+blockedOnDeadMVar :: SomeException -- for the RTS
+blockedOnDeadMVar = toException BlockedOnDeadMVar
+
 -----
 
+-- |The thread is awiting 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
     deriving Typeable
 
@@ -652,8 +663,13 @@ instance Exception BlockedIndefinitely
 instance Show BlockedIndefinitely where
     showsPrec _ BlockedIndefinitely = showString "thread blocked indefinitely"
 
+blockedIndefinitely :: SomeException -- for the RTS
+blockedIndefinitely = toException BlockedIndefinitely
+
 -----
 
+-- |There are no runnable threads, so the program is deadlocked.
+-- The @Deadlock@ exception is raised in the main thread only.
 data Deadlock = Deadlock
     deriving Typeable
 
@@ -664,6 +680,8 @@ instance Show Deadlock where
 
 -----
 
+-- |Exceptions generated by 'assert'. The @String@ gives information
+-- about the source location of the assertion.
 data AssertionFailed = AssertionFailed String
     deriving Typeable
 
@@ -674,7 +692,7 @@ instance Show AssertionFailed where
 
 -----
 
--- |Asynchronous exceptions
+-- |Asynchronous exceptions.
 data AsyncException
   = StackOverflow
         -- ^The current thread\'s stack exceeded its limit.
@@ -781,6 +799,7 @@ data IOException
      ioe_type     :: IOErrorType,    -- what it was.
      ioe_location :: String,         -- location.
      ioe_description :: String,      -- error type specific information.
+     ioe_errno    :: Maybe CInt,     -- errno leading to this error, if any.
      ioe_filename :: Maybe FilePath  -- filename the error is related to.
    }
     deriving Typeable
@@ -788,8 +807,8 @@ data IOException
 instance Exception IOException
 
 instance Eq IOException where
-  (IOError h1 e1 loc1 str1 fn1) == (IOError h2 e2 loc2 str2 fn2) = 
-    e1==e2 && str1==str2 && h1==h2 && loc1==loc2 && fn1==fn2
+  (IOError h1 e1 loc1 str1 en1 fn1) == (IOError h2 e2 loc2 str2 en2 fn2) = 
+    e1==e2 && str1==str2 && h1==h2 && loc1==loc2 && en1==en2 && fn1==fn2
 
 -- | An abstract type that contains a value for each variant of 'IOError'.
 data IOErrorType
@@ -814,13 +833,9 @@ data IOErrorType
   | TimeExpired
   | ResourceVanished
   | Interrupted
-  | DynIOError Dynamic -- cheap&cheerful extensible IO error type.
 
 instance Eq IOErrorType where
-   x == y = 
-     case x of
-       DynIOError{} -> False -- from a strictness POV, compatible with a derived Eq inst?
-       _ -> getTag x ==# getTag y
+   x == y = getTag x ==# getTag y
  
 instance Show IOErrorType where
   showsPrec _ e =
@@ -845,7 +860,6 @@ instance Show IOErrorType where
       TimeExpired       -> "timeout"
       UnsatisfiedConstraints -> "unsatisified constraints" -- ultra-precise!
       UnsupportedOperation -> "unsupported operation"
-      DynIOError{}      -> "unknown IO error"
 
 -- | Construct an 'IOError' value with a string describing the error.
 -- The 'fail' method of the 'IO' instance of the 'Monad' class raises a
@@ -856,13 +870,13 @@ instance Show IOErrorType where
 -- >   fail s = ioError (userError s)
 --
 userError       :: String  -> IOError
-userError str   =  IOError Nothing UserError "" str Nothing
+userError str   =  IOError Nothing UserError "" str Nothing Nothing
 
 -- ---------------------------------------------------------------------------
 -- Showing IOErrors
 
 instance Show IOException where
-    showsPrec p (IOError hdl iot loc s fn) =
+    showsPrec p (IOError hdl iot loc s _ fn) =
       (case fn of
          Nothing -> case hdl of
                         Nothing -> id
@@ -912,7 +926,7 @@ catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a
 catchAny (IO io) handler = IO $ catch# io handler'
     where handler' (SomeException e) = unIO (handler e)
 
--- | A variant of 'throw' that can be used within the 'IO' monad.
+-- | A variant of 'throw' that can only be used within the 'IO' monad.
 --
 -- Although 'throwIO' has a type that is an instance of the type of 'throw', the
 -- two functions are subtly different:
@@ -973,9 +987,10 @@ blocked = IO $ \s -> case asyncExceptionsBlocked# s of
 \end{code}
 
 \begin{code}
--- | Forces its argument to be evaluated when the resultant 'IO' action
--- is executed.  It can be used to order evaluation with respect to
--- other 'IO' operations; its semantics are given by
+-- | Forces its argument to be evaluated to weak head normal form when
+-- the resultant 'IO' action is executed. It can be used to order
+-- evaluation with respect to other 'IO' operations; its semantics are
+-- given by
 --
 -- >   evaluate x `seq` y    ==>  y
 -- >   evaluate x `catch` f  ==>  (return $! x) `catch` f