Safe Haskell | Safe-Infered |
---|
Allocate resources which are guaranteed to be released.
For more information, see http://www.yesodweb.com/blog/2011/12/resourcet.
One point to note: all register cleanup actions live in the base monad, not the main monad. This allows both more efficient code, and for monads to be transformed.
- data ResourceT m a
- data ReleaseKey
- runResourceT :: Resource m => ResourceT m a -> m a
- with :: Resource m => Base m a -> (a -> Base m ()) -> ResourceT m (ReleaseKey, a)
- withIO :: ResourceIO m => IO a -> (a -> IO ()) -> ResourceT m (ReleaseKey, a)
- register :: Resource m => Base m () -> ResourceT m ReleaseKey
- release :: Resource m => ReleaseKey -> ResourceT m ()
- readRef :: Resource m => Ref (Base m) a -> ResourceT m a
- writeRef :: Resource m => Ref (Base m) a -> a -> ResourceT m ()
- newRef :: Resource m => a -> ResourceT m (Ref (Base m) a)
- resourceForkIO :: ResourceIO m => ResourceT m () -> ResourceT m ThreadId
- transResourceT :: Base m ~ Base n => (m a -> n b) -> ResourceT m a -> ResourceT n b
- newtype ExceptionT m a = ExceptionT {
- runExceptionT :: m (Either SomeException a)
- runExceptionT_ :: Monad m => ExceptionT m a -> m a
- class (HasRef (Base m), Monad m) => Resource m where
- type Base m :: * -> *
- resourceLiftBase :: Base m a -> m a
- resourceBracket_ :: Base m () -> Base m () -> m c -> m c
- class Resource m => ResourceUnsafeIO m where
- unsafeFromIO :: IO a -> m a
- class (ResourceBaseIO (Base m), ResourceUnsafeIO m, ResourceThrow m, MonadIO m, MonadBaseControl IO m) => ResourceIO m
- class ResourceBaseIO m where
- safeFromIOBase :: IO a -> m a
- class Resource m => ResourceThrow m where
- resourceThrow :: Exception e => e -> m a
- class Monad m => HasRef m where
- data InvalidAccess = InvalidAccess {}
- resourceActive :: Resource m => ResourceT m Bool
Data types
The Resource transformer. This transformer keeps track of all registered
actions, and calls them upon exit (via runResourceT
). Actions may be
registered via register
, or resources may be allocated atomically via
with
or withIO
. The with functions correspond closely to bracket
.
Releasing may be performed before exit via the release
function. This is a
highly recommended optimization, as it will ensure that scarce resources are
freed early. Note that calling release
will deregister the action, so that
a release action will only ever be called once.
data ReleaseKey Source
Unwrap
runResourceT :: Resource m => ResourceT m a -> m aSource
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
Resource allocation
Perform some allocation, and automatically register a cleanup action.
If you are performing an IO
action, it will likely be easier to use the
withIO
function, which handles types more cleanly.
:: ResourceIO m | |
=> IO a | allocate |
-> (a -> IO ()) | free resource |
-> ResourceT m (ReleaseKey, a) |
Same as with
, but explicitly uses IO
as a base.
register :: Resource m => Base m () -> ResourceT m ReleaseKeySource
Register some action that will be called precisely once, either when
runResourceT
is called, or when the ReleaseKey
is passed to release
.
release :: Resource m => ReleaseKey -> ResourceT m ()Source
Call a release action early, and deregister it from the list of cleanup actions to be performed.
Use references
Special actions
resourceForkIO :: ResourceIO m => ResourceT m () -> ResourceT m ThreadIdSource
Introduce a reference-counting scheme to allow a resource context to be shared by multiple threads. Once the last thread exits, all remaining resources will be released.
Note that abuse of this function will greatly delay the deallocation of registered resources. This function should be used with care. A general guideline:
If you are allocating a resource that should be shared by multiple threads,
and will be held for a long time, you should allocate it at the beginning of
a new ResourceT
block and then call resourceForkIO
from there.
Monad transformation
transResourceT :: Base m ~ Base n => (m a -> n b) -> ResourceT m a -> ResourceT n bSource
Transform the monad a ResourceT
lives in. This is most often used to
strip or add new transformers to a stack, e.g. to run a ReaderT
. Note that
the original and new monad must both have the same Base
monad.
A specific Exception transformer
newtype ExceptionT m a Source
The express purpose of this transformer is to allow the ST
monad to
catch exceptions via the ResourceThrow
typeclass.
ExceptionT | |
|
MonadTrans ExceptionT | |
MonadTransControl ExceptionT | |
MonadBase b m => MonadBase b (ExceptionT m) | |
MonadBaseControl b m => MonadBaseControl b (ExceptionT m) | |
Monad m => Monad (ExceptionT m) | |
Monad m => Functor (ExceptionT m) | |
Monad m => Applicative (ExceptionT m) | |
(Resource m, MonadBaseControl (Base m) m) => ResourceThrow (ExceptionT m) |
runExceptionT_ :: Monad m => ExceptionT m a -> m aSource
Same as runExceptionT
, but immediately throw
any exception returned.
Type class/associated types
class (HasRef (Base m), Monad m) => Resource m whereSource
A Monad
with a base that has mutable references, and allows some way to
run base actions and clean up properly.
The base monad for the current monad stack. This will usually be IO
or ST
.
resourceLiftBase :: Base m a -> m aSource
Run some action in the Base
monad. This function corresponds to
liftBase
, but due to various type issues, we need to have our own
version here.
Guarantee that some initialization and cleanup code is called before and after some action. Note that the initialization and cleanup lives in the base monad, while the body is in the top monad.
class Resource m => ResourceUnsafeIO m whereSource
A Resource
based on some monad which allows running of some IO
actions, via unsafe calls. This applies to IO
and ST
, for instance.
unsafeFromIO :: IO a -> m aSource
ResourceUnsafeIO IO | |
(MonadTransControl t, ResourceUnsafeIO m, Monad (t m)) => ResourceUnsafeIO (t m) | |
ResourceUnsafeIO (ST s) | |
ResourceUnsafeIO (ST s) |
class (ResourceBaseIO (Base m), ResourceUnsafeIO m, ResourceThrow m, MonadIO m, MonadBaseControl IO m) => ResourceIO m Source
ResourceIO IO | |
(MonadTransControl t, ResourceIO m, Monad (t m), ResourceThrow (t m), MonadBaseControl IO (t m), MonadIO (t m)) => ResourceIO (t m) |
class ResourceBaseIO m whereSource
A helper class for ResourceIO
, stating that the base monad provides IO
actions.
safeFromIOBase :: IO a -> m aSource
class Resource m => ResourceThrow m whereSource
A Resource
which can throw exceptions. Note that this does not work in a
vanilla ST
monad. Instead, you should use the ExceptionT
transformer on
top of ST
.
resourceThrow :: Exception e => e -> m aSource
ResourceThrow IO | |
ResourceThrow m => ResourceThrow (MaybeT m) | |
ResourceThrow m => ResourceThrow (ListT m) | |
ResourceThrow m => ResourceThrow (IdentityT m) | |
(Resource m, MonadBaseControl (Base m) m) => ResourceThrow (ExceptionT m) | |
(Monoid w, ResourceThrow m) => ResourceThrow (WriterT w m) | |
(Monoid w, ResourceThrow m) => ResourceThrow (WriterT w m) | |
ResourceThrow m => ResourceThrow (StateT s m) | |
ResourceThrow m => ResourceThrow (StateT s m) | |
ResourceThrow m => ResourceThrow (ReaderT r m) | |
(Error e, ResourceThrow m) => ResourceThrow (ErrorT e m) | |
(Monoid w, ResourceThrow m) => ResourceThrow (RWST r w s m) | |
(Monoid w, ResourceThrow m) => ResourceThrow (RWST r w s m) |
Low-level
class Monad m => HasRef m whereSource
A base monad which provides mutable references and some exception-safe way
of interacting with them. For monads which cannot handle exceptions (e.g.,
ST
), exceptions may be ignored. However, in such cases, scarce resources
should not be allocated in those monads, as exceptions may cause the
cleanup functions to not run.
The instance for IO
, however, is fully exception-safe.
Minimal complete definition: Ref
, newRef'
, readRef'
and writeRef'
.
newRef' :: a -> m (Ref m a)Source
readRef' :: Ref m a -> m aSource
writeRef' :: Ref m a -> a -> m ()Source
atomicModifyRef' :: Ref m a -> (a -> (a, b)) -> m bSource
For monads supporting multi-threaded access (e.g., IO
), this much be
an atomic modification.
mask :: ((forall a. m a -> m a) -> m b) -> m bSource
try :: m a -> m (Either SomeException a)Source
data InvalidAccess Source
resourceActive :: Resource m => ResourceT m BoolSource
Determine if the current ResourceT
is still active. This is necessary
for such cases as lazy I/O, where an unevaluated thunk may still refer to a
closed ResourceT
.