| Safe Haskell | None |
|---|
Control.Monad.Interface.Mask
Description
This module exports:
- The
MonadMasktype class and its operationsgetMaskingStateandsetMaskingState. - Instances of
MonadMaskfor all the base monads in thebaseandtransformerspackages. - A universal pass-through instance of
MonadMaskfor any existingMonadMaskwrapped by aMonadLayer. - The utility operations
mask,mask_,uninterruptibleMask,uninterruptibleMask_.
- class Monad m => MonadMask m where
- getMaskingState :: m MaskingState
- setMaskingState :: MaskingState -> m a -> m a
- mask :: MonadMask m => ((forall a n. MonadMask n => n a -> n a) -> m b) -> m b
- mask_ :: MonadMask m => m a -> m a
- uninterruptibleMask :: MonadMask m => ((forall a n. MonadMask n => n a -> n a) -> m b) -> m b
- uninterruptibleMask_ :: MonadMask m => m a -> m a
Documentation
class Monad m => MonadMask m whereSource
The MonadMask type class is for dealing with asynchronous exceptions.
It contains the getMaskingState and setMaskingState operations for
getting and setting the MaskingState of the current thread. However, you
should never need to use these operations: in particular, using
setMaskingState can violate some invariants which are assumed internally
by this library. The only reason these functions are exposed at all is that
they are necessary to implement mask (which is what you should use
instead), and unlike mask, their simpler type signature allows us to
define a universal pass-through instance of MonadMask through any
MonadLayer, while mask would require
MonadLayerControl.
Every monad should be an instance of MonadMask, and we have provided
instances for every base monad in the base and transformers packages.
getMaskingState and setMaskingState have default definitions that only
need to be overridden in the case of IO and monads layered on top of IO
(which we have already done), so it costs nothing to add an instance of
MonadMask to a monad. (MonadMask is a prerequisite for implementing
MonadTry, which provides the
bracket family of functions, which is perhaps
more interesting than MonadMask on its own.)
Minimal complete definition: instance head only.
Methods
getMaskingState :: m MaskingStateSource
Returns the MaskingState for the current thread.
setMaskingState :: MaskingState -> m a -> m aSource
Sets the MaskingState for the current thread to the given value.
mask :: MonadMask m => ((forall a n. MonadMask n => n a -> n a) -> m b) -> m bSource
Executes a computation with asynchronous exceptions masked. That is,
any thread which attempts to raise an exception in the current thread with
throwTo will be blocked until asynchronous exceptions
are unmasked again.
The argument passed to mask is a function that takes as its argument
another function, which can be used to restore the prevailing masking state
within the context of the masked computation. For example, a common way to
use mask is to protect the acquisition of a resource:
mask $ \restore -> do
x <- acquire
restore (do_something_with x) `finally` release
This code guarantees that acquire is paired with release, by masking
asynchronous exceptions for the critical parts. (Rather than write this
code yourself, it would be better to use bracket which abstracts the
general pattern).
Note that the restore action passed to the argument to mask does not
necessarily unmask asynchronous exceptions, it just restores the masking
state to that of the enclosing context. Thus if asynchronous exceptions are
already masked, mask cannot be used to unmask exceptions again. This is
so that if you call a library function with exceptions masked, you can be
sure that the library call will not be able to unmask exceptions again. If
you are writing library code and need to use asynchronous exceptions, the
only way is to create a new thread; see
forkWithUnmask.
Asynchronous exceptions may still be received while in the masked state if the masked thread blocks in certain ways; see Control.Exception.
Threads created by fork inherit the masked
state from the parent; that is, to start a thread in blocked mode, use
mask_ $ fork .... This is particularly useful if you need to establish
an exception handler in the forked thread before any asynchronous
exceptions are received.
mask_ :: MonadMask m => m a -> m aSource
Like mask, but does not pass a restore action to the argument.
uninterruptibleMask :: MonadMask m => ((forall a n. MonadMask n => n a -> n a) -> m b) -> m bSource
Like mask, but the masked computation is not interruptible (see
Control.Exception). THIS SHOULD BE USED WITH GREAT CARE,
because if a thread executing in uninterruptibleMask blocks for any
reason, then the thread (and possibly the program, if this is the main
thread) will be unresponsive and unkillable. This function should only be
necessary if you need to mask exceptions around an interruptible operation,
and you can guarantee that the interruptible operation will only block for
a short period of time.
uninterruptibleMask_ :: MonadMask m => m a -> m aSource
Like uninterruptibleMask, but does not pass a restore action to the
argument.