Safe Haskell | None |
---|---|
Language | Haskell98 |
A generalization of Control.Exception from the IO
monad to
MonadRecover
SomeException
.
- type MonadThrow μ = MonadAbort SomeException μ
- exception :: Exception e => e -> α
- throw :: (MonadThrow μ, Exception e) => e -> μ α
- throwIO :: (MonadBase IO μ, Exception e) => e -> μ α
- ioError :: MonadBase IO μ => IOError -> μ α
- throwTo :: (MonadBase IO μ, Exception e) => ThreadId -> e -> μ ()
- type MonadCatch μ = MonadRecover SomeException μ
- catch :: (MonadCatch μ, Exception e) => μ α -> (e -> μ α) -> μ α
- handle :: (MonadCatch μ, Exception e) => (e -> μ α) -> μ α -> μ α
- catchJust :: (MonadCatch μ, Exception e) => (e -> Maybe β) -> μ α -> (β -> μ α) -> μ α
- handleJust :: (MonadCatch μ, Exception e) => (e -> Maybe β) -> (β -> μ α) -> μ α -> μ α
- data Handler μ α = Exception e => Handler (e -> μ α)
- catches :: MonadCatch μ => μ α -> [Handler μ α] -> μ α
- handles :: MonadCatch μ => [Handler μ α] -> μ α -> μ α
- try :: (MonadCatch μ, Exception e) => μ α -> μ (Either e α)
- tryJust :: (MonadCatch μ, Exception e) => (e -> Maybe β) -> μ α -> μ (Either β α)
- evaluateIO :: MonadBase IO μ => α -> μ α
- class (Applicative μ, Monad μ) => MonadMask μ where
- liftGetMaskingState :: (MonadMask μ, MonadTrans t) => t μ MaskingState
- liftWithMaskingState :: (MonadTransControl t, MonadMask μ, Monad (t μ)) => MaskingState -> t μ α -> t μ α
- mask :: forall μ α. MonadMask μ => ((forall η β. MonadMask η => η β -> η β) -> μ α) -> μ α
- mask_ :: forall μ α. MonadMask μ => μ α -> μ α
- uninterruptibleMask :: MonadMask μ => ((forall η β. MonadMask η => η β -> η β) -> μ α) -> μ α
- uninterruptibleMask_ :: MonadMask μ => μ α -> μ α
- interruptible :: MonadMask μ => μ α -> μ α
- allowInterrupt :: MonadMask μ => μ ()
- module Control.Monad.Abort.Class
- module Control.Monad.Finally
- module Control.Exception
Throwing exceptions
type MonadThrow μ = MonadAbort SomeException μ Source #
An alias for MonadAbort
SomeException
μ.
throw :: (MonadThrow μ, Exception e) => e -> μ α Source #
Throw an exception from monadic code. An alias for
.abort
. toException
throwTo :: (MonadBase IO μ, Exception e) => ThreadId -> e -> μ () Source #
Raise an exception in the target thread. See throwTo
.
Catching exceptions
type MonadCatch μ = MonadRecover SomeException μ Source #
An alias for MonadRecover
SomeException
μ.
catch :: (MonadCatch μ, Exception e) => μ α -> (e -> μ α) -> μ α Source #
Recover from the specified type of exceptions.
:: (MonadCatch μ, Exception e) | |
=> (e -> Maybe β) | Exception predicate |
-> μ α | Main computation |
-> (β -> μ α) | Exception handler |
-> μ α |
Recover from exceptions that satisfy the provided predicate.
handleJust :: (MonadCatch μ, Exception e) => (e -> Maybe β) -> (β -> μ α) -> μ α -> μ α Source #
Exception handler.
catches :: MonadCatch μ => μ α -> [Handler μ α] -> μ α Source #
Recover from exceptions by sequentually trying to apply the provided handlers.
try :: (MonadCatch μ, Exception e) => μ α -> μ (Either e α) Source #
Recover from exceptions of the spesified type, wrapping them into
Left
.
:: (MonadCatch μ, Exception e) | |
=> (e -> Maybe β) | Exception predicate |
-> μ α | Main compuration |
-> μ (Either β α) |
Recover from exceptions that satisfy the provided predicate, wrapping
them into Left
.
evaluateIO :: MonadBase IO μ => α -> μ α Source #
Evalute the argument to weak head normal form.
Asynchronous exception control
class (Applicative μ, Monad μ) => MonadMask μ where Source #
A class of monads that support masking of asynchronous exceptions.
getMaskingState :: μ MaskingState Source #
Get the current masking state.
getMaskingState :: (MonadMask η, MonadTrans t, μ ~ t η) => μ MaskingState Source #
Get the current masking state.
withMaskingState :: MaskingState -> μ α -> μ α Source #
Run the provided computation with the specified MaskingState
.
withMaskingState :: (MonadMask η, MonadTransControl t, μ ~ t η) => MaskingState -> μ α -> μ α Source #
Run the provided computation with the specified MaskingState
.
MonadMask IO Source # | |
MonadMask μ => MonadMask (MaybeT μ) Source # | |
MonadMask μ => MonadMask (ListT μ) Source # | |
MonadMask μ => MonadMask (ExceptT e μ) Source # | |
MonadMask μ => MonadMask (AbortT e μ) Source # | |
MonadMask μ => MonadMask (FinishT β μ) Source # | |
(MonadMask μ, Monoid w) => MonadMask (WriterT w μ) Source # | |
MonadMask μ => MonadMask (StateT s μ) Source # | |
(MonadMask μ, Error e) => MonadMask (ErrorT e μ) Source # | |
MonadMask μ => MonadMask (StateT s μ) Source # | |
(MonadMask μ, Monoid w) => MonadMask (WriterT w μ) Source # | |
MonadMask μ => MonadMask (ReaderT * r μ) Source # | |
(MonadMask μ, Monoid w) => MonadMask (RWST r w s μ) Source # | |
(MonadMask μ, Monoid w) => MonadMask (RWST r w s μ) Source # | |
liftGetMaskingState :: (MonadMask μ, MonadTrans t) => t μ MaskingState Source #
Lift getMaskingState
through a monad transformer.
liftWithMaskingState :: (MonadTransControl t, MonadMask μ, Monad (t μ)) => MaskingState -> t μ α -> t μ α Source #
Lift withMaskingState
through a monad transformer.
mask :: forall μ α. MonadMask μ => ((forall η β. MonadMask η => η β -> η β) -> μ α) -> μ α Source #
Prevents asynchronous exceptions from being raised within the provided
computation. Blocking operations can still be interrupted. Supplies the
computation with
, where withMaskingState
ss
is the current masking
state.
uninterruptibleMask :: MonadMask μ => ((forall η β. MonadMask η => η β -> η β) -> μ α) -> μ α Source #
Prevents asynchronous exceptions from being raised within the provided
computation. Also prevents blocking operations from being interrupted.
Supplies the computation with
, where withMaskingState
ss
is the
current masking state.
uninterruptibleMask_ :: MonadMask μ => μ α -> μ α Source #
An alias for
.uninterruptibleMask
. const
interruptible :: MonadMask μ => μ α -> μ α Source #
Allow asynchronous exceptions to be raised within the provided
computation, even if the current masking state is MaskedInterruptible
(but not in MaskedUninterruptible
state).
allowInterrupt :: MonadMask μ => μ () Source #
An alias for
.interruptible
(return
())
Re-exports
module Control.Monad.Abort.Class
module Control.Monad.Finally
module Control.Exception