Copyright | (c) The University of Glasgow 2009 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | libraries@haskell.org |
Stability | internal |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
IO-related Exception types and functions
Synopsis
- data BlockedIndefinitelyOnMVar = BlockedIndefinitelyOnMVar
- blockedIndefinitelyOnMVar :: SomeException
- data BlockedIndefinitelyOnSTM = BlockedIndefinitelyOnSTM
- blockedIndefinitelyOnSTM :: SomeException
- data Deadlock = Deadlock
- data AllocationLimitExceeded = AllocationLimitExceeded
- allocationLimitExceeded :: SomeException
- newtype AssertionFailed = AssertionFailed String
- newtype CompactionFailed = CompactionFailed String
- cannotCompactFunction :: SomeException
- cannotCompactPinned :: SomeException
- cannotCompactMutable :: SomeException
- data SomeAsyncException = forall e.Exception e => SomeAsyncException e
- asyncExceptionToException :: Exception e => e -> SomeException
- asyncExceptionFromException :: Exception e => SomeException -> Maybe e
- data AsyncException
- stackOverflow :: SomeException
- heapOverflow :: SomeException
- data ArrayException
- data ExitCode
- data FixIOException = FixIOException
- ioException :: IOException -> IO a
- ioError :: IOError -> IO a
- type IOError = IOException
- data IOException = IOError {}
- data IOErrorType
- userError :: String -> IOError
- assertError :: (?callStack :: CallStack) => Bool -> a -> a
- unsupportedOperation :: IOError
- untangle :: Addr# -> String -> String
Documentation
data BlockedIndefinitelyOnMVar Source #
The thread is blocked on an MVar
, but there are no other references
to the MVar
so it can't ever continue.
Instances
Show BlockedIndefinitelyOnMVar Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception BlockedIndefinitelyOnMVar Source # | Since: 4.1.0.0 |
data BlockedIndefinitelyOnSTM Source #
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.
Instances
Show BlockedIndefinitelyOnSTM Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception BlockedIndefinitelyOnSTM Source # | Since: 4.1.0.0 |
There are no runnable threads, so the program is deadlocked.
The Deadlock
exception is raised in the main thread only.
Instances
Show Deadlock Source # | Since: 4.1.0.0 |
Exception Deadlock Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception toException :: Deadlock -> SomeException Source # fromException :: SomeException -> Maybe Deadlock Source # displayException :: Deadlock -> String Source # |
data AllocationLimitExceeded Source #
This thread has exceeded its allocation limit. See
setAllocationCounter
and
enableAllocationLimit
.
Since: 4.8.0.0
Instances
Show AllocationLimitExceeded Source # | Since: 4.7.1.0 |
Defined in GHC.IO.Exception | |
Exception AllocationLimitExceeded Source # | Since: 4.8.0.0 |
newtype AssertionFailed Source #
Instances
Show AssertionFailed Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception AssertionFailed Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception |
newtype CompactionFailed Source #
Compaction found an object that cannot be compacted. Functions
cannot be compacted, nor can mutable objects or pinned objects.
See compact
.
Since: 4.10.0.0
Instances
Show CompactionFailed Source # | Since: 4.10.0.0 |
Defined in GHC.IO.Exception | |
Exception CompactionFailed Source # | Since: 4.10.0.0 |
Defined in GHC.IO.Exception |
data SomeAsyncException Source #
Superclass for asynchronous exceptions.
Since: 4.7.0.0
forall e.Exception e => SomeAsyncException e |
Instances
Show SomeAsyncException Source # | Since: 4.7.0.0 |
Defined in GHC.IO.Exception | |
Exception SomeAsyncException Source # | Since: 4.7.0.0 |
Defined in GHC.IO.Exception |
asyncExceptionToException :: Exception e => e -> SomeException Source #
Since: 4.7.0.0
asyncExceptionFromException :: Exception e => SomeException -> Maybe e Source #
Since: 4.7.0.0
data AsyncException Source #
Asynchronous exceptions.
StackOverflow | The current thread's stack exceeded its limit. Since an exception has been raised, the thread's stack will certainly be below its limit again, but the programmer should take remedial action immediately. |
HeapOverflow | The program's heap is reaching its limit, and the program should take action to reduce the amount of live data it has. Notes:
|
ThreadKilled | This exception is raised by another thread
calling |
UserInterrupt | This exception is raised by default in the main thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console). |
Instances
Eq AsyncException Source # | Since: 4.2.0.0 |
Defined in GHC.IO.Exception (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool # | |
Ord AsyncException Source # | Since: 4.2.0.0 |
Defined in GHC.IO.Exception compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException # | |
Show AsyncException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception AsyncException Source # | Since: 4.7.0.0 |
Defined in GHC.IO.Exception |
data ArrayException Source #
Exceptions generated by array operations
IndexOutOfBounds String | An attempt was made to index an array outside its declared bounds. |
UndefinedElement String | An attempt was made to evaluate an element of an array that had not been initialized. |
Instances
Eq ArrayException Source # | Since: 4.2.0.0 |
Defined in GHC.IO.Exception (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Ord ArrayException Source # | Since: 4.2.0.0 |
Defined in GHC.IO.Exception compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # | |
Show ArrayException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception ArrayException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception |
Defines the exit codes that a program can return.
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Eq ExitCode Source # | |
Ord ExitCode Source # | |
Defined in GHC.IO.Exception | |
Read ExitCode Source # | |
Show ExitCode Source # | |
Generic ExitCode Source # | |
Exception ExitCode Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException Source # fromException :: SomeException -> Maybe ExitCode Source # displayException :: ExitCode -> String Source # | |
type Rep ExitCode Source # | |
Defined in GHC.IO.Exception type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
data FixIOException Source #
The exception thrown when an infinite cycle is detected in
fixIO
.
Since: 4.11.0.0
Instances
Show FixIOException Source # | Since: 4.11.0.0 |
Defined in GHC.IO.Exception | |
Exception FixIOException Source # | Since: 4.11.0.0 |
Defined in GHC.IO.Exception |
ioException :: IOException -> IO a Source #
type IOError = IOException Source #
data IOException Source #
Exceptions that occur in the IO
monad.
An IOException
records a more specific error type, a descriptive
string and maybe the handle that was used when the error was
flagged.
IOError | |
|
Instances
Eq IOException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOException -> IOException -> Bool # (/=) :: IOException -> IOException -> Bool # | |
Show IOException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception | |
Exception IOException Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception |
data IOErrorType Source #
An abstract type that contains a value for each variant of IOError
.
Instances
Eq IOErrorType Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOErrorType -> IOErrorType -> Bool # (/=) :: IOErrorType -> IOErrorType -> Bool # | |
Show IOErrorType Source # | Since: 4.1.0.0 |
Defined in GHC.IO.Exception |
assertError :: (?callStack :: CallStack) => Bool -> a -> a Source #