resourcet-1.2.1: Deterministic allocation and freeing of scarce resources.

Safe HaskellNone
LanguageHaskell98

Control.Monad.Trans.Resource

Contents

Description

Allocate resources which are guaranteed to be released.

For more information, see https://www.fpcomplete.com/user/snoyberg/library-documentation/resourcet.

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.

Synopsis

Data types

data ResourceT m a Source #

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
MonadTrans ResourceT Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

lift :: Monad m => m a -> ResourceT m a #

MonadRWS r w s m => MonadRWS r w s (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

MonadWriter w m => MonadWriter w (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

writer :: (a, w) -> ResourceT m a #

tell :: w -> ResourceT m () #

listen :: ResourceT m a -> ResourceT m (a, w) #

pass :: ResourceT m (a, w -> w) -> ResourceT m a #

MonadState s m => MonadState s (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

get :: ResourceT m s #

put :: s -> ResourceT m () #

state :: (s -> (a, s)) -> ResourceT m a #

MonadReader r m => MonadReader r (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

ask :: ResourceT m r #

local :: (r -> r) -> ResourceT m a -> ResourceT m a #

reader :: (r -> a) -> ResourceT m a #

MonadError e m => MonadError e (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwError :: e -> ResourceT m a #

catchError :: ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a #

Monad m => Monad (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

(>>=) :: ResourceT m a -> (a -> ResourceT m b) -> ResourceT m b #

(>>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

return :: a -> ResourceT m a #

fail :: String -> ResourceT m a #

Functor m => Functor (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

fmap :: (a -> b) -> ResourceT m a -> ResourceT m b #

(<$) :: a -> ResourceT m b -> ResourceT m a #

MonadFix m => MonadFix (ResourceT m) Source #

Since: resourcet-1.1.8

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mfix :: (a -> ResourceT m a) -> ResourceT m a #

Applicative m => Applicative (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

pure :: a -> ResourceT m a #

(<*>) :: ResourceT m (a -> b) -> ResourceT m a -> ResourceT m b #

liftA2 :: (a -> b -> c) -> ResourceT m a -> ResourceT m b -> ResourceT m c #

(*>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

(<*) :: ResourceT m a -> ResourceT m b -> ResourceT m a #

MonadIO m => MonadIO (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftIO :: IO a -> ResourceT m a #

Alternative m => Alternative (ResourceT m) Source #

Since 1.1.5

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

empty :: ResourceT m a #

(<|>) :: ResourceT m a -> ResourceT m a -> ResourceT m a #

some :: ResourceT m a -> ResourceT m [a] #

many :: ResourceT m a -> ResourceT m [a] #

MonadPlus m => MonadPlus (ResourceT m) Source #

Since 1.1.5

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mzero :: ResourceT m a #

mplus :: ResourceT m a -> ResourceT m a -> ResourceT m a #

MonadThrow m => MonadThrow (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadCatch m => MonadCatch (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

catch :: Exception e => ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a #

MonadMask m => MonadMask (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

uninterruptibleMask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

generalBracket :: ResourceT m a -> (a -> ExitCase b -> ResourceT m c) -> (a -> ResourceT m b) -> ResourceT m (b, c) #

MonadCont m => MonadCont (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

callCC :: ((a -> ResourceT m b) -> ResourceT m a) -> ResourceT m a #

PrimMonad m => PrimMonad (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Associated Types

type PrimState (ResourceT m) :: * #

Methods

primitive :: (State# (PrimState (ResourceT m)) -> (#State# (PrimState (ResourceT m)), a#)) -> ResourceT m a #

MonadUnliftIO m => MonadUnliftIO (ResourceT m) Source #

Since: resourcet-1.1.10

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

askUnliftIO :: ResourceT m (UnliftIO (ResourceT m)) #

withRunInIO :: ((forall a. ResourceT m a -> IO a) -> IO b) -> ResourceT m b #

MonadIO m => MonadResource (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

type PrimState (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

type ResIO = ResourceT IO Source #

Convenient alias for ResourceT IO.

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

Unwrap

runResourceT :: MonadUnliftIO m => ResourceT m a -> m a Source #

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.

NOTE Since version 1.2.0, this function will throw a ResourceCleanupException if any of the cleanup functions throw an exception.

Since: resourcet-0.3.0

Check cleanup exceptions

runResourceTChecked :: MonadUnliftIO m => ResourceT m a -> m a Source #

Backwards compatible alias for runResourceT.

Since: resourcet-1.1.11

data ResourceCleanupException Source #

Thrown when one or more cleanup functions themselves throw an exception during cleanup.

Since: resourcet-1.1.11

Constructors

ResourceCleanupException 

Fields

Special actions

resourceForkWith :: MonadUnliftIO m => (IO () -> IO a) -> ResourceT m () -> ResourceT m a Source #

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.

The first parameter is a function which will be used to create the thread, such as forkIO or async.

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 resourceForkWith from there.

Since: resourcet-1.1.9

resourceForkIO :: MonadUnliftIO m => ResourceT m () -> ResourceT m ThreadId Source #

Launch a new reference counted resource context using forkIO.

This is defined as resourceForkWith forkIO.

Since: resourcet-0.3.0

Monad transformation

transResourceT :: (m a -> n b) -> ResourceT m a -> ResourceT n b Source #

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 a Source #

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

allocate Source #

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 ReleaseKey Source #

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 allows 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 b Source #

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 MonadIO m => MonadResource m where Source #

A Monad which allows for safe resource allocation. In theory, any monad transformer stack which includes a ResourceT can be an instance of MonadResource.

Note: runResourceT has a requirement for a MonadUnliftIO 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

Minimal complete definition

liftResourceT

Methods

liftResourceT :: ResourceT IO a -> m a Source #

Lift a ResourceT IO action into the current Monad.

Since 0.4.0

Instances
MonadResource m => MonadResource (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

MonadResource m => MonadResource (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ListT m a Source #

MonadIO m => MonadResource (ResourceT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

MonadResource m => MonadResource (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ExceptT e m a Source #

MonadResource m => MonadResource (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

MonadResource m => MonadResource (StateT s m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> StateT s m a Source #

MonadResource m => MonadResource (StateT s m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> StateT s m a Source #

(Monoid w, MonadResource m) => MonadResource (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> WriterT w m a Source #

(Monoid w, MonadResource m) => MonadResource (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> WriterT w m a Source #

MonadResource m => MonadResource (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ContT r m a Source #

MonadResource m => MonadResource (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ReaderT r m a Source #

(Monoid w, MonadResource m) => MonadResource (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> RWST r w s m a Source #

(Monoid w, MonadResource m) => MonadResource (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> RWST r w s m a Source #

type MonadResourceBase = MonadUnliftIO Source #

Deprecated: Use MonadUnliftIO directly instead

Just use MonadUnliftIO directly now, legacy explanation continues:

A Monad which can be used as a base for a ResourceT.

A ResourceT has some restrictions on its base monad:

  • runResourceT requires an instance of MonadUnliftIO.
  • MonadResource requires an instance of MonadIO

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 MonadIO m => MonadUnliftIO (m :: * -> *) #

Monads which allow their actions to be run in IO.

While MonadIO allows an IO action to be lifted into another monad, this class captures the opposite concept: allowing you to capture the monadic context. Note that, in order to meet the laws given below, the intuition is that a monad must have no monadic state, but may have monadic context. This essentially limits MonadUnliftIO to ReaderT and IdentityT transformers on top of IO.

Laws. For any value u returned by askUnliftIO, it must meet the monad transformer laws as reformulated for MonadUnliftIO:

  • unliftIO u . return = return
  • unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f

The third is a currently nameless law which ensures that the current context is preserved.

  • askUnliftIO >>= (u -> liftIO (unliftIO u m)) = m

If you have a name for this, please submit it in a pull request for great glory.

Since: unliftio-core-0.1.0.0

Minimal complete definition

askUnliftIO | withRunInIO

Instances
MonadUnliftIO IO 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

askUnliftIO :: IO (UnliftIO IO) #

withRunInIO :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

MonadUnliftIO m => MonadUnliftIO (ResourceT m) #

Since: resourcet-1.1.10

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

askUnliftIO :: ResourceT m (UnliftIO (ResourceT m)) #

withRunInIO :: ((forall a. ResourceT m a -> IO a) -> IO b) -> ResourceT m b #

MonadUnliftIO m => MonadUnliftIO (IdentityT m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

askUnliftIO :: IdentityT m (UnliftIO (IdentityT m)) #

withRunInIO :: ((forall a. IdentityT m a -> IO a) -> IO b) -> IdentityT m b #

MonadUnliftIO m => MonadUnliftIO (ReaderT r m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

askUnliftIO :: ReaderT r m (UnliftIO (ReaderT r m)) #

withRunInIO :: ((forall a. ReaderT r m a -> IO a) -> IO b) -> ReaderT r m b #

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 ReleaseMap Source #

The internal state held by a ResourceT transformer.

Since 0.4.6

getInternalState :: Monad m => ResourceT m InternalState Source #

Get the internal state of the current ResourceT.

Since 0.4.6

runInternalState :: ResourceT m a -> InternalState -> m a Source #

Unwrap a ResourceT using the given InternalState.

Since 0.4.6

withInternalState :: (InternalState -> m a) -> ResourceT m a Source #

Run an action in the underlying monad, providing it the InternalState.

Since 0.4.6

createInternalState :: MonadIO m => m InternalState Source #

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 :: MonadIO m => InternalState -> m () Source #

Close an internal state created by createInternalState.

Since 0.4.9

Reexport

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.

Minimal complete definition

throwM

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 [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> STM a #

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ResourceT m) # 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #