| Safe Haskell | None |
|---|
Control.Monad.Interface.Try
Description
This module exports:
- The
MonadTrytype class and its operationmtry. - Instances of
MonadTryfor all the base monads in thebaseandtransformerspackages. - A universal pass-through instance of
MonadMaskfor any existingMonadMaskwrapped by aMonadLayerControl. - The utility operations
bracket,bracket_,bracketOnError,finallyandonException.
- class MonadMask m => MonadTry m where
- bracket :: MonadTry m => m a -> (a -> m b) -> (a -> m c) -> m c
- bracket_ :: MonadTry m => m a -> m b -> m c -> m c
- bracketOnError :: MonadTry m => m a -> (a -> m b) -> (a -> m c) -> m c
- finally :: MonadTry m => m a -> m b -> m a
- onException :: MonadTry m => m a -> m b -> m a
Documentation
class MonadMask m => MonadTry m whereSource
The MonadTry type class provides a single operation mtry, which is a
way to observe short-circuiting in monads. The name refers to the fact that
mtry is a generalised version of try:
whereas try guards against the specific case of a
MonadException short-circuiting due to
an exception being thrown, it can still short-circuit in other ways: e.g.,
if a returns
MaybeT IOmzero (Nothing). The action returned by mtry is
guaranteed to never short-circuit.
Nearly every monad should have an instance of MonadTry, with the
exception of CPS-style monads whose (possible) short-circuiting is
impossible to observe. Instances for every base monad in the base and
transformers packages. mtry has a default definition that only needs
to be overridden for monads which actually short-circuit, so it costs
very little to add an instance of MonadTry to a monad.
Minimal complete definition: instance head only.
Methods
mtry :: m a -> m (Either (m a) a)Source
mtry takes a monadic action in m and returns a new monadic value
in m which is guaranteed not to short-circuit. If the action m that
was given to mtry would have short-circuited, it returns Left m,
otherwise it returns Right a, where a is the value returned by the
computation m.
Arguments
| :: MonadTry m | |
| => m a | computation to run first ("acquire resource") |
| -> (a -> m b) | computation to run last ("release resource") |
| -> (a -> m c) | computation to run in-between |
| -> m c | returns the value from the in-between computation |
When you want to acquire a resource, do some work with it, and then
release the resource, it is a good idea to use bracket, because bracket
will install the necessary handler to release the resource in the event
that the monad short circuits during the computation. If the monad
short-circuits, then bracket will re-return the monad in its
short-circuited state (after performing the release).
A common example is opening a file:
bracket
(openFile "filename" ReadMode)
(hClose)
(\fileHandle -> do { ... })
The arguments to bracket are in this order so that we can partially apply
it, e.g.:
withFile name mode = bracket (openFile name mode) hClose
bracket_ :: MonadTry m => m a -> m b -> m c -> m cSource
A variant of bracket where the return value from the first computation
is not required.
bracketOnError :: MonadTry m => m a -> (a -> m b) -> (a -> m c) -> m cSource
Like bracket, but only performs the final action if the monad
short-circuited during the in-between computation.
finally :: MonadTry m => m a -> m b -> m aSource
A specialised variant of bracket with just a computation to run
afterward.
onException :: MonadTry m => m a -> m b -> m aSource
Like finally, but only performs the final action if the monad
short-circuited during the computation.