resourcet-extra-0.1.1: ResourceT extras
Safe HaskellSafe-Inferred
LanguageGHC2021

Control.Monad.Trans.Resource.Extra

Synopsis

Acquire

acquire1 :: ((forall x. IO x -> IO x) -> IO a) -> (a -> IO ()) -> Acquire a Source #

Like mkAcquire1, but the acquire function is provided the current Restore-like function.

acquireType1 :: ((forall x. IO x -> IO x) -> IO a) -> (a -> ReleaseType -> IO ()) -> Acquire a Source #

Like mkAcquireType1, but the acquire function is provided the current Restore-like function.

mkAcquire1 :: IO a -> (a -> IO ()) -> Acquire a Source #

Like mkAcquire, but the release function will be run at most once. Subsequent executions of the release function will be no-ops.

mkAcquireType1 :: IO a -> (a -> ReleaseType -> IO ()) -> Acquire a Source #

Like mkAcquireType, but the release function will be run at most once. Subsequent executions of the release function will be no-ops.

acquireReleaseSelf :: Acquire ((ReleaseType -> IO ()) -> a) -> Acquire a Source #

Build an Acquire having access to its own release function.

The release function will be run at most once. Subsequent executions of the release function will be no-ops.

unAcquire Source #

Arguments

:: MonadIO m 
=> Acquire a 
-> (forall x. IO x -> IO x)

Restore-like function.

-> m (a, ReleaseType -> IO ()) 

Removes the Acquire and Allocated wrappers.

MonadResource

registerType :: MonadResource m => (ReleaseType -> IO ()) -> m ReleaseKey Source #

Like register, but gives access to the ReleaseType too.

releaseType :: MonadIO m => ReleaseKey -> ReleaseType -> m () Source #

Like release, but allows specifying the ReleaseType too.

unprotectType :: MonadIO m => ReleaseKey -> m (Maybe (ReleaseType -> IO ())) Source #

Like unprotect, but allows specifying the ReleaseType too.

acquireReleaseKey :: ReleaseKey -> Acquire () Source #

acquireReleaseKey will unprotectType the ReleaseKey, and use Acquire to manage the release action instead.

MonadMask

runResourceT :: (MonadMask m, MonadIO m) => ResourceT m a -> m a Source #

Like runResourceT, but requires only MonadMask.

withAcquire :: (MonadMask m, MonadIO m) => Acquire a -> (a -> m b) -> m b Source #

Like withAcquireRelease, but doesn't take the extra release function.

withAcquireRelease :: (MonadMask m, MonadIO m) => Acquire a -> ((ReleaseType -> IO ()) -> a -> m b) -> m b Source #

withAcquireRelease acq \release a -> act acquires the a and automaticaly releases it when mb returns or throws an exception. If desired, release can be used to release a earlier.

Restore

newtype Restore m Source #

Wrapper around a “restore” function like the one given by mask (\restore -> ...), in a particular Monad m.

Constructors

Restore (forall x. m x -> m x) 

getRestoreIO :: MonadIO m => m (Restore IO) Source #

Get the current Restore action in IO, wrapped in Restore.

withRestoreIO :: (MonadMask m, MonadIO m) => ((forall x. IO x -> IO x) -> m a) -> m a Source #

Get the current Restore action in IO, without the Restore wrapper.

Async

asyncRestore Source #

Arguments

:: MonadUnliftIO m 
=> Bool

Whether to link the Async.

-> ((forall x. IO x -> IO x) -> ResourceT m a)

You may use liftIOOp on this Restore-like function.

-> ResourceT m (ReleaseKey, Async a) 

Like resourceFork, but uses Async to communicate with the background thread.

The Async is initially masked. A Restore-like function is provided to restore to the call-site masking state.

As a convenience, the Async may optionally be safely linked by this function, too.

IO

once :: (MonadIO m, MonadIO n, MonadMask n) => n () -> m (n ()) Source #

once ma creates a wrapper for ma which will execute ma at most once. Further executions of the same wrapped ma are a no-op. It's safe to attempt to use the wrapper concurrently; only one thread will get to execute the actual ma at most.

onceK :: (MonadIO m, MonadIO n, MonadMask n) => (a -> n ()) -> m (a -> n ()) Source #

Kleisli version of once.