safe-exceptions-0.1.7.4: Safe, consistent, and easy exception handling
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Exception.Safe

Description

Please see the README.md file in the safe-exceptions repo for information on how to use this module. Relevant links:

Synopsis

Throwing

throw :: (MonadThrow m, Exception e) => e -> m a Source #

Synchronously throw the given exception

Since: 0.1.0.0

throwIO :: (MonadThrow m, Exception e) => e -> m a Source #

Synonym for throw

Since: 0.1.0.0

throwM :: (MonadThrow m, Exception e) => e -> m a Source #

Synonym for throw

Since: 0.1.0.0

throwString :: (MonadThrow m, HasCallStack) => String -> m a Source #

A convenience function for throwing a user error. This is useful for cases where it would be too high a burden to define your own exception type.

This throws an exception of type StringException. When GHC supports it (base 4.9 and GHC 8.0 and onward), it includes a call stack.

Since: 0.1.5.0

data StringException Source #

Exception type thrown by throwString.

Note that the second field of the data constructor depends on GHC/base version. For base 4.9 and GHC 8.0 and later, the second field is a call stack. Previous versions of GHC and base do not support call stacks, and the field is simply unit (provided to make pattern matching across GHC versions easier).

Since: 0.1.5.0

Constructors

StringException String CallStack 

Instances

Instances details
Exception StringException Source # 
Instance details

Defined in Control.Exception.Safe

Show StringException Source # 
Instance details

Defined in Control.Exception.Safe

Methods

showsPrec :: Int -> StringException -> ShowS

show :: StringException -> String

showList :: [StringException] -> ShowS

throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m () Source #

Throw an asynchronous exception to another thread.

Synchronously typed exceptions will be wrapped into an AsyncExceptionWrapper, see https://github.com/fpco/safe-exceptions#determining-sync-vs-async

It's usually a better idea to use the async package, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

impureThrow :: Exception e => e -> a Source #

Generate a pure value which, when forced, will synchronously throw the given exception

Generally it's better to avoid using this function and instead use throw, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

Catching (with recovery)

catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a Source #

Same as upstream catch, but will not catch asynchronous exceptions

Since: 0.1.0.0

catchIO :: MonadCatch m => m a -> (IOException -> m a) -> m a Source #

catch specialized to only catching IOExceptions

Since: 0.1.3.0

catchAny :: MonadCatch m => m a -> (SomeException -> m a) -> m a Source #

catch specialized to catch all synchronous exception

Since: 0.1.0.0

catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> (e -> m a) -> m a Source #

Same as catch, but fully force evaluation of the result value to find all impure exceptions.

Since: 0.1.1.0

catchAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> (SomeException -> m a) -> m a Source #

catchDeep specialized to catch all synchronous exception

Since: 0.1.1.0

catchAsync :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a Source #

catch without async exception safety

Generally it's better to avoid using this function since we do not want to recover from async exceptions, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

catchJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a Source #

catchJust is like catch but it takes an extra argument which is an exception predicate, a function which selects which type of exceptions we're interested in.

Since: 0.1.4.0

handle :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a Source #

Flipped version of catch

Since: 0.1.0.0

handleIO :: MonadCatch m => (IOException -> m a) -> m a -> m a Source #

handle specialized to only catching IOExceptions

Since: 0.1.3.0

handleAny :: MonadCatch m => (SomeException -> m a) -> m a -> m a Source #

Flipped version of catchAny

Since: 0.1.0.0

handleDeep :: (MonadCatch m, Exception e, MonadIO m, NFData a) => (e -> m a) -> m a -> m a Source #

Flipped version of catchDeep

Since: 0.1.1.0

handleAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => (SomeException -> m a) -> m a -> m a Source #

Flipped version of catchAnyDeep

Since: 0.1.1.0

handleAsync :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a Source #

Flipped version of catchAsync

Generally it's better to avoid using this function since we do not want to recover from async exceptions, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

handleJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a Source #

Flipped catchJust.

Since: 0.1.4.0

try :: (MonadCatch m, Exception e) => m a -> m (Either e a) Source #

Same as upstream try, but will not catch asynchronous exceptions

Since: 0.1.0.0

tryIO :: MonadCatch m => m a -> m (Either IOException a) Source #

try specialized to only catching IOExceptions

Since: 0.1.3.0

tryAny :: MonadCatch m => m a -> m (Either SomeException a) Source #

try specialized to catch all synchronous exceptions

Since: 0.1.0.0

tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => m a -> m (Either e a) Source #

Same as try, but fully force evaluation of the result value to find all impure exceptions.

Since: 0.1.1.0

tryAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either SomeException a) Source #

tryDeep specialized to catch all synchronous exceptions

Since: 0.1.1.0

tryAsync :: (MonadCatch m, Exception e) => m a -> m (Either e a) Source #

try without async exception safety

Generally it's better to avoid using this function since we do not want to recover from async exceptions, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.0.0

tryJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a) Source #

A variant of try that takes an exception predicate to select which exceptions are caught.

Since: 0.1.4.0

data Handler (m :: Type -> Type) a #

Constructors

Exception e => Handler (e -> m a) 

Instances

Instances details
Monad m => Functor (Handler m) 
Instance details

Defined in Control.Monad.Catch

Methods

fmap :: (a -> b) -> Handler m a -> Handler m b

(<$) :: a -> Handler m b -> Handler m a

catches :: (MonadCatch m, MonadThrow m) => m a -> [Handler m a] -> m a Source #

Same as upstream catches, but will not catch asynchronous exceptions

Since: 0.1.2.0

catchesDeep :: (MonadCatch m, MonadThrow m, MonadIO m, NFData a) => m a -> [Handler m a] -> m a Source #

Same as catches, but fully force evaluation of the result value to find all impure exceptions.

Since: 0.1.2.0

catchesAsync :: (MonadCatch m, MonadThrow m) => m a -> [Handler m a] -> m a Source #

catches without async exception safety

Generally it's better to avoid using this function since we do not want to recover from async exceptions, see https://github.com/fpco/safe-exceptions#quickstart

Since: 0.1.2.0

Cleanup (no recovery)

onException :: MonadMask m => m a -> m b -> m a Source #

Async safe version of onException

Since: 0.1.0.0

bracket :: forall m a b c. MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c Source #

Async safe version of bracket

Since: 0.1.0.0

bracket_ :: MonadMask m => m a -> m b -> m c -> m c Source #

Async safe version of bracket_

Since: 0.1.0.0

finally :: MonadMask m => m a -> m b -> m a Source #

Async safe version of finally

Since: 0.1.0.0

withException :: (MonadMask m, Exception e) => m a -> (e -> m b) -> m a Source #

Like onException, but provides the handler the thrown exception.

Since: 0.1.0.0

bracketOnError :: forall m a b c. MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c Source #

Async safe version of bracketOnError

Since: 0.1.0.0

bracketOnError_ :: MonadMask m => m a -> m b -> m c -> m c Source #

A variant of bracketOnError where the return value from the first computation is not required.

Since: 0.1.0.0

bracketWithError :: forall m a b c. MonadMask m => m a -> (Maybe SomeException -> a -> m b) -> (a -> m c) -> m c Source #

Async safe version of bracket with access to the exception in the cleanup action.

Since: 0.1.7.0

Coercion to sync and async

data SyncExceptionWrapper Source #

Wrap up an asynchronous exception to be treated as a synchronous exception

This is intended to be created via toSyncException

Since: 0.1.0.0

Constructors

forall e.Exception e => SyncExceptionWrapper e 

toSyncException :: Exception e => e -> SomeException Source #

Convert an exception into a synchronous exception

For synchronous exceptions, this is the same as toException. For asynchronous exceptions, this will wrap up the exception with SyncExceptionWrapper

Since: 0.1.0.0

data AsyncExceptionWrapper Source #

Wrap up a synchronous exception to be treated as an asynchronous exception

This is intended to be created via toAsyncException

Since: 0.1.0.0

Constructors

forall e.Exception e => AsyncExceptionWrapper e 

toAsyncException :: Exception e => e -> SomeException Source #

Convert an exception into an asynchronous exception

For asynchronous exceptions, this is the same as toException. For synchronous exceptions, this will wrap up the exception with AsyncExceptionWrapper

Since: 0.1.0.0

Check exception type

isSyncException :: Exception e => e -> Bool Source #

Check if the given exception is synchronous

Since: 0.1.0.0

isAsyncException :: Exception e => e -> Bool Source #

Check if the given exception is asynchronous

Since: 0.1.0.0

Reexports

class Monad m => MonadThrow (m :: Type -> Type) #

Minimal complete definition

throwM

Instances

Instances details
MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> STM a

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IO a

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Q a

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a

MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a]

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ST s a

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a

MonadThrow m => MonadThrow (MaybeT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a

(Error e, MonadThrow m) => MonadThrow (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a

MonadThrow m => MonadThrow (ExceptT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a

class MonadThrow m => MonadCatch (m :: Type -> Type) #

Minimal complete definition

catch

Instances

Instances details
MonadCatch STM 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a

MonadCatch IO 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a

e ~ SomeException => MonadCatch (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => Either e a -> (e0 -> Either e a) -> Either e a

MonadCatch m => MonadCatch (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a

MonadCatch m => MonadCatch (MaybeT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a

(Error e, MonadCatch m) => MonadCatch (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ErrorT e m a -> (e0 -> ErrorT e m a) -> ErrorT e m a

MonadCatch m => MonadCatch (ExceptT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ExceptT e m a -> (e0 -> ExceptT e m a) -> ExceptT e m a

MonadCatch m => MonadCatch (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a

MonadCatch m => MonadCatch (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a

class MonadCatch m => MonadMask (m :: Type -> Type) where #

Methods

mask :: ((forall a. m a -> m a) -> m b) -> m b #

uninterruptibleMask :: ((forall a. m a -> m a) -> m b) -> m b #

generalBracket :: m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c) #

Instances

Instances details
MonadMask IO 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

generalBracket :: IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c) #

e ~ SomeException => MonadMask (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

generalBracket :: Either e a -> (a -> ExitCase b -> Either e c) -> (a -> Either e b) -> Either e (b, c) #

MonadMask m => MonadMask (MaybeT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

uninterruptibleMask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

generalBracket :: MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) #

(Error e, MonadMask m) => MonadMask (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

uninterruptibleMask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

generalBracket :: ErrorT e m a -> (a -> ExitCase b -> ErrorT e m c) -> (a -> ErrorT e m b) -> ErrorT e m (b, c) #

MonadMask m => MonadMask (ExceptT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

MonadMask m => MonadMask (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

generalBracket :: IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

mask_ :: MonadMask m => m a -> m a #

uninterruptibleMask_ :: MonadMask m => m a -> m a #

catchIOError :: MonadCatch m => m a -> (IOError -> m a) -> m a #

handleIOError :: MonadCatch m => (IOError -> m a) -> m a -> m a #

class (Typeable e, Show e) => Exception e where #

Minimal complete definition

Nothing

Methods

toException :: e -> SomeException #

fromException :: SomeException -> Maybe e #

displayException :: e -> String #

Instances

Instances details
Exception ErrorCall 
Instance details

Defined in GHC.Exception

Methods

toException :: ErrorCall -> SomeException #

fromException :: SomeException -> Maybe ErrorCall #

displayException :: ErrorCall -> String #

Exception ArithException 
Instance details

Defined in GHC.Exception.Type

Methods

toException :: ArithException -> SomeException #

fromException :: SomeException -> Maybe ArithException #

displayException :: ArithException -> String #

Exception SomeException 
Instance details

Defined in GHC.Exception.Type

Exception AllocationLimitExceeded 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: AllocationLimitExceeded -> SomeException #

fromException :: SomeException -> Maybe AllocationLimitExceeded #

displayException :: AllocationLimitExceeded -> String #

Exception ArrayException 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: ArrayException -> SomeException #

fromException :: SomeException -> Maybe ArrayException #

displayException :: ArrayException -> String #

Exception AssertionFailed 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: AssertionFailed -> SomeException #

fromException :: SomeException -> Maybe AssertionFailed #

displayException :: AssertionFailed -> String #

Exception AsyncException 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: AsyncException -> SomeException #

fromException :: SomeException -> Maybe AsyncException #

displayException :: AsyncException -> String #

Exception BlockedIndefinitelyOnMVar 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: BlockedIndefinitelyOnMVar -> SomeException #

fromException :: SomeException -> Maybe BlockedIndefinitelyOnMVar #

displayException :: BlockedIndefinitelyOnMVar -> String #

Exception BlockedIndefinitelyOnSTM 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: BlockedIndefinitelyOnSTM -> SomeException #

fromException :: SomeException -> Maybe BlockedIndefinitelyOnSTM #

displayException :: BlockedIndefinitelyOnSTM -> String #

Exception CompactionFailed 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: CompactionFailed -> SomeException #

fromException :: SomeException -> Maybe CompactionFailed #

displayException :: CompactionFailed -> String #

Exception Deadlock 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: Deadlock -> SomeException #

fromException :: SomeException -> Maybe Deadlock #

displayException :: Deadlock -> String #

Exception ExitCode 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: ExitCode -> SomeException #

fromException :: SomeException -> Maybe ExitCode #

displayException :: ExitCode -> String #

Exception FixIOException 
Instance details

Defined in GHC.IO.Exception

Methods

toException :: FixIOException -> SomeException #

fromException :: SomeException -> Maybe FixIOException #

displayException :: FixIOException -> String #

Exception IOException 
Instance details

Defined in GHC.IO.Exception

Exception SomeAsyncException 
Instance details

Defined in GHC.IO.Exception

Exception AsyncExceptionWrapper Source # 
Instance details

Defined in Control.Exception.Safe

Exception StringException Source # 
Instance details

Defined in Control.Exception.Safe

Exception SyncExceptionWrapper Source # 
Instance details

Defined in Control.Exception.Safe

class Typeable (a :: k) #

Minimal complete definition

typeRep#

data SomeException #

Constructors

Exception e => SomeException e 

Instances

Instances details
Exception SomeException 
Instance details

Defined in GHC.Exception.Type

Show SomeException 
Instance details

Defined in GHC.Exception.Type

Methods

showsPrec :: Int -> SomeException -> ShowS

show :: SomeException -> String

showList :: [SomeException] -> ShowS

data SomeAsyncException #

Constructors

Exception e => SomeAsyncException e 

Instances

Instances details
Exception SomeAsyncException 
Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException 
Instance details

Defined in GHC.IO.Exception

Methods

showsPrec :: Int -> SomeAsyncException -> ShowS

show :: SomeAsyncException -> String

showList :: [SomeAsyncException] -> ShowS

data IOException #

Instances

Instances details
Exception IOException 
Instance details

Defined in GHC.IO.Exception

Show IOException 
Instance details

Defined in GHC.IO.Exception

Methods

showsPrec :: Int -> IOException -> ShowS

show :: IOException -> String

showList :: [IOException] -> ShowS

Eq IOException 
Instance details

Defined in GHC.IO.Exception

Methods

(==) :: IOException -> IOException -> Bool

(/=) :: IOException -> IOException -> Bool

Error IOException 
Instance details

Defined in Control.Monad.Trans.Error

Methods

noMsg :: IOException

strMsg :: String -> IOException

assert :: Bool -> a -> a #