| Safe Haskell | None | 
|---|
Control.Monad.Trans.Resource
Contents
Description
Allocate resources which are guaranteed to be released.
For more information, see http://www.yesodweb.com/book/conduits.
One point to note: all register cleanup actions live in the IO monad, not
 the main monad. This allows both more efficient code, and for monads to be
 transformed.
- data ResourceT m a
- type ResIO a = ResourceT IO a
- data ReleaseKey
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
- resourceForkIO :: MonadBaseControl IO m => ResourceT m () -> ResourceT m ThreadId
- transResourceT :: (m a -> n b) -> ResourceT m a -> ResourceT n b
- joinResourceT :: ResourceT (ResourceT m) a -> ResourceT m a
- allocate :: MonadResource m => IO a -> (a -> IO ()) -> m (ReleaseKey, a)
- register :: MonadResource m => IO () -> m ReleaseKey
- release :: MonadIO m => ReleaseKey -> m ()
- unprotect :: MonadIO m => ReleaseKey -> m (Maybe (IO ()))
- resourceMask :: MonadResource m => ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> m b
- class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m  where- liftResourceT :: ResourceT IO a -> m a
 
- type MonadResourceBase m = (MonadBaseControl IO m, MonadThrow m, MonadBase IO m, MonadIO m, Applicative m)
- data InvalidAccess = InvalidAccess {}
- class MonadBase b m => MonadBaseControl b m | m -> b
- type InternalState = IORef ReleaseMap
- getInternalState :: Monad m => ResourceT m InternalState
- runInternalState :: ResourceT m a -> InternalState -> m a
- withInternalState :: (InternalState -> m a) -> ResourceT m a
- createInternalState :: MonadBase IO m => m InternalState
- closeInternalState :: MonadBase IO m => InternalState -> m ()
- type ExceptionT = CatchT
- runExceptionT :: ExceptionT m a -> m (Either SomeException a)
- runExceptionT_ :: Monad m => ExceptionT m a -> m a
- runException :: ExceptionT Identity a -> Either SomeException a
- runException_ :: ExceptionT Identity a -> a
- class Monad m => MonadThrow m where
- monadThrow :: (Exception e, MonadThrow m) => e -> m a
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
 allocate. allocate corresponds 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.
Since 0.3.0
Instances
| MFunctor ResourceT | Since 0.4.7 | 
| MMonad ResourceT | Since 0.4.7 | 
| MonadTrans ResourceT | |
| MonadTransControl ResourceT | |
| MonadRWS r w s m => MonadRWS r w s (ResourceT m) | |
| MonadBase b m => MonadBase b (ResourceT m) | |
| MonadBaseControl b m => MonadBaseControl b (ResourceT m) | |
| MonadError e m => MonadError e (ResourceT m) | |
| MonadReader r m => MonadReader r (ResourceT m) | |
| MonadState s m => MonadState s (ResourceT m) | |
| MonadWriter w m => MonadWriter w (ResourceT m) | |
| Monad m => Monad (ResourceT m) | |
| Functor m => Functor (ResourceT m) | |
| Typeable1 m => Typeable1 (ResourceT m) | |
| Applicative m => Applicative (ResourceT m) | |
| MonadThrow m => MonadThrow (ResourceT m) | |
| MonadCatch m => MonadCatch (ResourceT m) | |
| MonadMask m => MonadMask (ResourceT m) | |
| MonadIO m => MonadIO (ResourceT m) | |
| MonadCont m => MonadCont (ResourceT m) | |
| (MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | 
data ReleaseKey Source
A lookup key for a specific release action. This value is returned by
 register and allocate, and is passed to release.
Since 0.3.0
Instances
Unwrap
runResourceT :: MonadBaseControl IO 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.
Since 0.3.0
Special actions
resourceForkIO :: MonadBaseControl IO 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.
Since 0.3.0
Monad transformation
transResourceT :: (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 this function is a slight generalization of hoist.
Since 0.3.0
joinResourceT :: ResourceT (ResourceT m) a -> ResourceT m aSource
This function mirrors join at the transformer level: it will collapse
 two levels of ResourceT into a single ResourceT.
Since 0.4.6
Registering/releasing
Arguments
| :: MonadResource m | |
| => IO a | allocate | 
| -> (a -> IO ()) | free resource | 
| -> m (ReleaseKey, a) | 
Perform some allocation, and automatically register a cleanup action.
This is almost identical to calling the allocation and then
 registering the release action, but this properly handles masking of
 asynchronous exceptions.
Since 0.3.0
register :: MonadResource m => IO () -> m ReleaseKeySource
Register some action that will be called precisely once, either when
 runResourceT is called, or when the ReleaseKey is passed to release.
Since 0.3.0
release :: MonadIO m => ReleaseKey -> m ()Source
Call a release action early, and deregister it from the list of cleanup actions to be performed.
Since 0.3.0
unprotect :: MonadIO m => ReleaseKey -> m (Maybe (IO ()))Source
Unprotect resource from cleanup actions, this allowes you to send resource into another resourcet process and reregister it there. It returns an release action that should be run in order to clean resource or Nothing in case if resource is already freed.
Since 0.4.5
resourceMask :: MonadResource m => ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> m bSource
Perform asynchronous exception masking.
This is more general then Control.Exception.mask, yet more efficient
 than Control.Exception.Lifted.mask.
Since 0.3.0
Type class/associated types
class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m whereSource
A Monad which allows for safe resource allocation. In theory, any monad
 transformer stack included a ResourceT can be an instance of
 MonadResource.
Note: runResourceT has a requirement for a MonadBaseControl IO m monad,
 which allows control operations to be lifted. A MonadResource does not
 have this requirement. This means that transformers such as ContT can be
 an instance of MonadResource. However, the ContT wrapper will need to be
 unwrapped before calling runResourceT.
Since 0.3.0
Methods
liftResourceT :: ResourceT IO a -> m aSource
Lift a ResourceT IO action into the current Monad.
Since 0.4.0
Instances
| MonadResource m => MonadResource (ListT m) | |
| MonadResource m => MonadResource (MaybeT m) | |
| MonadResource m => MonadResource (IdentityT m) | |
| (MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
| MonadResource m => MonadResource (ContT r m) | |
| (Error e, MonadResource m) => MonadResource (ErrorT e m) | |
| MonadResource m => MonadResource (ReaderT r m) | |
| MonadResource m => MonadResource (StateT s m) | |
| MonadResource m => MonadResource (StateT s m) | |
| (Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
| (Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
| (Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
| (Monoid w, MonadResource m) => MonadResource (RWST r w s m) | 
type MonadResourceBase m = (MonadBaseControl IO m, MonadThrow m, MonadBase IO m, MonadIO m, Applicative m)Source
A Monad which can be used as a base for a ResourceT.
A ResourceT has some restrictions on its base monad:
-  runResourceTrequires an instance ofMonadBaseControl IO. *MonadResourcerequires an instance ofMonadThrow,MonadIO, andApplicative.
While any instance of MonadBaseControl IO should be an instance of the
 other classes, this is not guaranteed by the type system (e.g., you may have
 a transformer in your stack with does not implement MonadThrow). Ideally,
 we would like to simply create an alias for the five type classes listed,
 but this is not possible with GHC currently.
Instead, this typeclass acts as a proxy for the other five. Its only purpose is to make your type signatures shorter.
Note that earlier versions of conduit had a typeclass ResourceIO. This
 fulfills much the same role.
Since 0.3.2
Low-level
data InvalidAccess Source
Indicates either an error in the library, or misuse of it (e.g., a
 ResourceT's state is accessed after being released).
Since 0.3.0
Constructors
| InvalidAccess | |
| Fields | |
Re-exports
class MonadBase b m => MonadBaseControl b m | m -> b
Instances
Internal state
A ResourceT internally is a modified ReaderT monad transformer holding
 onto a mutable reference to all of the release actions still remaining to be
 performed. If you are building up a custom application monad, it may be more
 efficient to embed this ReaderT functionality directly in your own monad
 instead of wrapping around ResourceT itself. This section provides you the
 means of doing so.
type InternalState = IORef ReleaseMapSource
The internal state held by a ResourceT transformer.
Since 0.4.6
getInternalState :: Monad m => ResourceT m InternalStateSource
Get the internal state of the current ResourceT.
Since 0.4.6
runInternalState :: ResourceT m a -> InternalState -> m aSource
Unwrap a ResourceT using the given InternalState.
Since 0.4.6
withInternalState :: (InternalState -> m a) -> ResourceT m aSource
Run an action in the underlying monad, providing it the InternalState.
Since 0.4.6
createInternalState :: MonadBase IO m => m InternalStateSource
Create a new internal state. This state must be closed with
 closeInternalState. It is your responsibility to ensure exception safety.
 Caveat emptor!
Since 0.4.9
closeInternalState :: MonadBase IO m => InternalState -> m ()Source
Close an internal state created by createInternalState.
Since 0.4.9
Backwards compatibility
type ExceptionT = CatchTSource
For backwards compatibility.
runExceptionT :: ExceptionT m a -> m (Either SomeException a)Source
For backwards compatibility.
runExceptionT_ :: Monad m => ExceptionT m a -> m aSource
Same as runExceptionT, but immediately throw any exception returned.
Since 0.3.0
runException :: ExceptionT Identity a -> Either SomeException aSource
Run an ExceptionT Identity stack.
Since 0.4.2
runException_ :: ExceptionT Identity a -> aSource
Run an ExceptionT Identity stack, but immediately throw any exception returned.
Since 0.4.2
class Monad m => MonadThrow m where
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Methods
throwM :: Exception e => e -> m a
Throw an exception. Note that this throws when this action is run in
 the monad m, not when it is applied. It is a generalization of
 Control.Exception's throwIO.
Should satisfy the law:
throwM e >> f = throwM e
Instances
| MonadThrow [] | |
| MonadThrow IO | |
| MonadThrow Maybe | |
| ~ * e SomeException => MonadThrow (Either e) | |
| Monad m => MonadThrow (CatchT m) | |
| MonadThrow m => MonadThrow (ListT m) | |
| MonadThrow m => MonadThrow (MaybeT m) | Throws exceptions into the base monad. | 
| MonadThrow m => MonadThrow (IdentityT m) | |
| MonadThrow m => MonadThrow (ResourceT m) | |
| MonadThrow m => MonadThrow (ContT r m) | |
| (Error e, MonadThrow m) => MonadThrow (ErrorT e m) | Throws exceptions into the base monad. | 
| MonadThrow m => MonadThrow (ReaderT r m) | |
| MonadThrow m => MonadThrow (StateT s m) | |
| MonadThrow m => MonadThrow (StateT s m) | |
| (MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
| (MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
| (MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
| (MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | 
monadThrow :: (Exception e, MonadThrow m) => e -> m aSource
Backwards compatibility