Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Mask m a where
- data MaskMode
- mask :: Eff Mask m => ((forall x. m x -> m x) -> m a) -> m a
- mask_ :: Eff Mask m => m a -> m a
- uninterruptibleMask :: Eff Mask m => ((forall x. m x -> m x) -> m a) -> m a
- uninterruptibleMask_ :: Eff Mask m => m a -> m a
- maskToIO :: (Carrier m, MonadMask m) => MaskToIOC m a -> m a
- ignoreMask :: Carrier m => IgnoreMaskC m a -> m a
- threadMaskViaClass :: forall t m a. Monad m => (RepresentationalT t, forall b. MonadMask b => MonadMask (t b)) => (forall x. Mask m x -> m x) -> Mask (t m) a -> t m a
- class MonadCatch m => MonadMask (m :: Type -> Type)
- type MaskToIOC = InterpretPrimC MaskToIOH Mask
- type IgnoreMaskC = InterpretC IgnoreMaskH Mask
Effects
An effect for masking asynchronous exceptions.
Mask
is typically used as a primitive effect.
If you define a Carrier
that relies on a novel
non-trivial monad transformer t
, then you need to make
a
instance (if possible).
ThreadsEff
t Mask
threadMaskViaClass
can help you with that.
The following threading constraints accept Mask
:
Instances
Actions
uninterruptibleMask :: Eff Mask m => ((forall x. m x -> m x) -> m a) -> m a Source #
uninterruptibleMask_ :: Eff Mask m => m a -> m a Source #
Interpretations
ignoreMask :: Carrier m => IgnoreMaskC m a -> m a Source #
Run a Mask
effect by ignoring it, providing no protection
against asynchronous exceptions.
Derivs
(IgnoreMaskC
m) =Mask
':Derivs
m
Prims
(IgnoreMaskC
m) =Prims
m
Threading utilities
threadMaskViaClass :: forall t m a. Monad m => (RepresentationalT t, forall b. MonadMask b => MonadMask (t b)) => (forall x. Mask m x -> m x) -> Mask (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance,
given that ThreadsEff
t Mask
t
lifts
.MonadMask
BEWARE: threadMaskViaClass
is only safe if the implementation of
mask
and uninterruptibleMask
for t m
only makes use of mask
and uninterruptibleMask
for m
, and no other methods of
MonadThrow
, MonadCatch
, and MonadMask
.
MonadMask
class MonadCatch m => MonadMask (m :: Type -> Type) #
A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.
Instances should ensure that, in the following code:
fg = f `finally` g
The action g
is called regardless of what occurs within f
, including
async exceptions. Some monads allow f
to abort the computation via other
effects than throwing an exception. For simplicity, we will consider aborting
and throwing an exception to be two forms of "throwing an error".
If f
and g
both throw an error, the error thrown by fg
depends on which
errors we're talking about. In a monad transformer stack, the deeper layers
override the effects of the inner layers; for example, ExceptT e1 (Except
e2) a
represents a value of type Either e2 (Either e1 a)
, so throwing both
an e1
and an e2
will result in Left e2
. If f
and g
both throw an
error from the same layer, instances should ensure that the error from g
wins.
Effects other than throwing an error are also overriden by the deeper layers.
For example, StateT s Maybe a
represents a value of type s -> Maybe (a,
s)
, so if an error thrown from f
causes this function to return Nothing
,
any changes to the state which f
also performed will be erased. As a
result, g
will see the state as it was before f
. Once g
completes,
f
's error will be rethrown, so g
' state changes will be erased as well.
This is the normal interaction between effects in a monad transformer stack.
By contrast, lifted-base's
version of finally
always discards all of g
's non-IO effects, and g
never sees any of f
's non-IO effects, regardless of the layer ordering and
regardless of whether f
throws an error. This is not the result of
interacting effects, but a consequence of MonadBaseControl
's approach.
Instances
Carriers
type MaskToIOC = InterpretPrimC MaskToIOH Mask Source #
type IgnoreMaskC = InterpretC IgnoreMaskH Mask Source #