Copyright | Copyright 2022 Shea Levy. |
---|---|
License | Apache-2.0 |
Maintainer | shea@shealevy.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines interfaces for safe resource usage on top of GeneralAllocate
,
where resource cleanup happens at the end of a lexical scope.
For contexts where nested scope-based allocation and release is insufficient, see Control.Monad.Allocate.
Synopsis
- class Monad m => MonadWith m where
- type WithException m
- stateThreadingGeneralWith :: GeneralAllocate m (WithException m) releaseReturn b a -> (a -> m b) -> m (b, releaseReturn)
- type With m = GeneralAllocate m (WithException m) ()
- generalWith :: MonadWith m => With m b a -> (a -> m b) -> m b
- onFailure :: MonadWith m => m a -> (WithException m -> m b) -> m a
- generalFinally :: MonadWith m => m a -> m b -> m (a, b)
- class (MonadWith m, Exceptable (WithException m)) => MonadWithExceptable m
- newtype WithNoContinuation m a = WithNoContinuation (m a)
Documentation
class Monad m => MonadWith m where Source #
A monad allowing for exception-safe resource usage within a lexical scope.
The guarantees of MonadWith
are weaker than MonadMask
: in some
monads, it's possible for resources not to get cleaned up if the entire monadic
computation is going to be aborted (e.g. an async exception sent to a thread executing a monad
with no exception catching). Of course, MonadMask
itself can't guarantee
cleanup in the presence of SIGKILL
... In any case, this allows for MonadWith
to be implemented
lawfully in more monads (see WithNoContinuation
). In particular, the MonadWith
instances for
IO
, ST
, and Identity
allow for writing monad-generic exception-safe code which can be properly
instantiated in IO
or mocked out in ST
/Identity
without changing the code.
type WithException m Source #
Data characterizing exceptional exit from the scope.
type WithException m = SomeException
stateThreadingGeneralWith Source #
:: GeneralAllocate m (WithException m) releaseReturn b a | Allocate the resource |
-> (a -> m b) | Use the resource |
-> m (b, releaseReturn) |
Allocate, use, and release a resource in some scope, threading through some state.
If resource acquisition succeeds, the resource is guaranteed to be released
if the monadic computation itself is going to continue. This is weaker than
the guarantees of generalBracket
, which can't be
implemented in monads without exception catching.
See generalWith
for the common use case where state threading isn't needed.
Instances
type With m = GeneralAllocate m (WithException m) () Source #
Describe the allocation and release of a resource.
A specialization of GeneralAllocate
for the most
common case with MonadWith
, see generalWith
.
Allocate, use, and release a resource in some scope.
If resource acquisition succeeds, the resource is guaranteed to be released
if the monadic computation itself is going to continue. This is weaker than
the guarantees of generalBracket
, which can't be
implemented in monads without exception catching.
:: MonadWith m | |
=> m a | Main action |
-> (WithException m -> m b) | Failure action |
-> m a |
Run some action if the first action fails.
Exception propagation will continue after the failure action runs.
If failure occurs, the failure action is guaranteed to run
if the monadic compuation itself is going to continue. This is
weaker than the guranatess of onError
, which can't
be implemented in monads without exception catching.
:: MonadWith m | |
=> m a | Main action |
-> m b | Final action |
-> m (a, b) |
Run some action after another one completes in an exception-safe manner.
The final action is guaranteed to run
if the monadic compuation itself is going to continue. This is
weaker than the guranatess of finally
, which can't
be implemented in monads without exception catching.
class (MonadWith m, Exceptable (WithException m)) => MonadWithExceptable m Source #
A MonadWith
whose exception type can be projected into the Haskell exception hierarchy
Instances
(MonadWith m, Exceptable (WithException m)) => MonadWithExceptable m Source # | |
Defined in Control.Monad.With |
newtype WithNoContinuation m a Source #
A helper for DerivingVia a
MonadWith
and MonadWithExceptable
instance for any Monad
.
Note that the derived instance is only valid if the monad satisfies the "no continuation" condition, i.e. that if execution of a computation exits a given lexical scope we are guaranteed that either all of the actions within that scope have executed or the entire monadic computation has been terminated.
The most common factors violating "no continuation" are call/cc and exception catching. A monad which allows exception throwing but not catching is not thereby disqualified, as any thrown exception will of necessity propagate until it terminates the entire monadic computation.
WithNoContinuation (m a) |