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 |
GHC.IO.Exception
Description
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 {
- ioe_handle :: Maybe Handle
- ioe_type :: IOErrorType
- ioe_location :: String
- ioe_description :: String
- ioe_errno :: Maybe CInt
- ioe_filename :: Maybe FilePath
- data IOErrorType
- = AlreadyExists
- | NoSuchThing
- | ResourceBusy
- | ResourceExhausted
- | EOF
- | IllegalOperation
- | PermissionDenied
- | UserError
- | UnsatisfiedConstraints
- | SystemError
- | ProtocolError
- | OtherError
- | InvalidArgument
- | InappropriateType
- | HardwareFault
- | UnsupportedOperation
- | TimeExpired
- | ResourceVanished
- | Interrupted
- 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.
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
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.
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
There are no runnable threads, so the program is deadlocked.
The Deadlock
exception is raised in the main thread only.
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
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: base-4.8.0.0
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
newtype AssertionFailed Source #
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: AssertionFailed -> SomeException Source #
fromException :: SomeException -> Maybe AssertionFailed Source #
Instance details
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: base-4.10.0.0
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: CompactionFailed -> SomeException Source #
fromException :: SomeException -> Maybe CompactionFailed Source #
Instance details
Defined in GHC.IO.Exception
data SomeAsyncException Source #
Superclass for asynchronous exceptions.
Since: base-4.7.0.0
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: SomeAsyncException -> SomeException Source #
fromException :: SomeException -> Maybe SomeAsyncException Source #
Instance details
Defined in GHC.IO.Exception
asyncExceptionToException :: Exception e => e -> SomeException Source #
Since: base-4.7.0.0
asyncExceptionFromException :: Exception e => SomeException -> Maybe e Source #
Since: base-4.7.0.0
data AsyncException Source #
Asynchronous exceptions.
Constructors
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.
The program's heap is reaching its limit, and the program should take action to reduce the amount of live data it has. Notes:
- It is undefined which thread receives this exception.
GHC currently throws this to the same thread that
receives
UserInterrupt
, but this may change in the future. - The GHC RTS currently can only recover from heap overflow if it detects that an explicit memory limit (set via RTS flags). has been exceeded. Currently, failure to allocate memory from the operating system results in immediate termination of the program.
This exception is raised by another thread
calling killThread
, or by the system
if it needs to terminate the thread for some
reason.
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
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: AsyncException -> SomeException Source #
fromException :: SomeException -> Maybe AsyncException Source #
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: AsyncException -> AsyncException -> Bool Source #
(/=) :: AsyncException -> AsyncException -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
compare :: AsyncException -> AsyncException -> Ordering Source #
(<) :: AsyncException -> AsyncException -> Bool Source #
(<=) :: AsyncException -> AsyncException -> Bool Source #
(>) :: AsyncException -> AsyncException -> Bool Source #
(>=) :: AsyncException -> AsyncException -> Bool Source #
max :: AsyncException -> AsyncException -> AsyncException Source #
min :: AsyncException -> AsyncException -> AsyncException Source #
data ArrayException Source #
Exceptions generated by array operations
Constructors
An attempt was made to evaluate an element of an array that had not been initialized.
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: ArrayException -> SomeException Source #
fromException :: SomeException -> Maybe ArrayException Source #
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: ArrayException -> ArrayException -> Bool Source #
(/=) :: ArrayException -> ArrayException -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
compare :: ArrayException -> ArrayException -> Ordering Source #
(<) :: ArrayException -> ArrayException -> Bool Source #
(<=) :: ArrayException -> ArrayException -> Bool Source #
(>) :: ArrayException -> ArrayException -> Bool Source #
(>=) :: ArrayException -> ArrayException -> Bool Source #
max :: ArrayException -> ArrayException -> ArrayException Source #
min :: ArrayException -> ArrayException -> ArrayException Source #
Defines the exit codes that a program can return.
Constructors
indicates successful termination;
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
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: ExitCode -> SomeException Source #
fromException :: SomeException -> Maybe ExitCode Source #
displayException :: ExitCode -> String Source #
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
data FixIOException Source #
The exception thrown when an infinite cycle is detected in
fixIO
.
Since: base-4.11.0.0
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: FixIOException -> SomeException Source #
fromException :: SomeException -> Maybe FixIOException Source #
Instance details
Defined in GHC.IO.Exception
ioException :: IOException -> IO a Source #
type IOError = IOException Source #
The Haskell 2010 type for exceptions in the IO
monad.
Any I/O operation may raise an IOException
instead of returning a result.
For a more general type of exception, including also those that arise
in pure code, see Exception
.
In Haskell 2010, this is an opaque type.
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.
Constructors
Fields
- ioe_handle :: Maybe Handle
- ioe_type :: IOErrorType
- ioe_location :: String
- ioe_description :: String
- ioe_errno :: Maybe CInt
- ioe_filename :: Maybe FilePath
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Methods
toException :: IOException -> SomeException Source #
fromException :: SomeException -> Maybe IOException Source #
displayException :: IOException -> String Source #
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: IOException -> IOException -> Bool Source #
(/=) :: IOException -> IOException -> Bool Source #
data IOErrorType Source #
An abstract type that contains a value for each variant of IOException
.
Constructors
Instances
Instances details
Instance details
Defined in GHC.IO.Exception
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: IOErrorType -> IOErrorType -> Bool Source #
(/=) :: IOErrorType -> IOErrorType -> Bool Source #
userError :: String -> IOError Source #
Construct an IOException
value with a string describing the error.
The fail
method of the IO
instance of the Monad
class raises a
userError
, thus:
instance Monad IO where ... fail s = ioError (userError s)
assertError :: (?callStack :: CallStack) => Bool -> a -> a Source #