module GHC.IOBase  (
    IO(..), unIO, failIO, liftIO, bindIO, thenIO, returnIO,
    unsafePerformIO, unsafeInterleaveIO,
    unsafeDupablePerformIO, unsafeDupableInterleaveIO,
    noDuplicate,
        
    stToIO, ioToST, unsafeIOToST, unsafeSTToIO,
        
    IORef(..), newIORef, readIORef, writeIORef,
    IOArray(..), newIOArray, readIOArray, writeIOArray, unsafeReadIOArray, unsafeWriteIOArray,
    MVar(..),
        
    FilePath,
    Handle(..), Handle__(..), HandleType(..), IOMode(..), FD,
    isReadableHandleType, isWritableHandleType, isReadWriteHandleType, showHandle,
        
    
    BufferList(..), BufferMode(..),
    
        
    Exception(..), ArithException(..), AsyncException(..), ArrayException(..),
    stackOverflow, heapOverflow, ioException,
    IOError, IOException(..), IOErrorType(..), ioError, userError,
    ExitCode(..),
    throwIO, block, unblock, blocked, catchAny, catchException,
    evaluate,
    ErrorCall(..), AssertionFailed(..), assertError, untangle,
    BlockedOnDeadMVar(..), BlockedIndefinitely(..), Deadlock(..),
    blockedOnDeadMVar, blockedIndefinitely
  ) where
import GHC.Base
import GHC.Exception
import GHC.IO
import GHC.IO.Handle.Types
import GHC.IO.IOMode
import GHC.IO.Exception
import GHC.IOArray
import GHC.IORef
import GHC.MVar
import Foreign.C.Types
import Data.Typeable
type FD = CInt
data BlockedOnDeadMVar = BlockedOnDeadMVar
    deriving Typeable
instance Exception BlockedOnDeadMVar
instance Show BlockedOnDeadMVar where
    showsPrec _ BlockedOnDeadMVar = showString "thread blocked indefinitely"
blockedOnDeadMVar :: SomeException 
blockedOnDeadMVar = toException BlockedOnDeadMVar
data BlockedIndefinitely = BlockedIndefinitely
    deriving Typeable
instance Exception BlockedIndefinitely
instance Show BlockedIndefinitely where
    showsPrec _ BlockedIndefinitely = showString "thread blocked indefinitely"
blockedIndefinitely :: SomeException 
blockedIndefinitely = toException BlockedIndefinitely