resourcet-effectful-1.0.1.0: Adaptation of the resourcet library for the effectful ecosystem.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Resource

Description

Resource management via MonadResource.

Synopsis

Effect

data Resource :: Effect Source #

Provide the ability to use the MonadResource instance of Eff.

Instances

Instances details
type DispatchOf Resource Source # 
Instance details

Defined in Effectful.Resource

newtype StaticRep Resource Source # 
Instance details

Defined in Effectful.Resource

Handlers

runResource :: IOE :> es => Eff (Resource ': es) a -> Eff es a Source #

Run the resource effect.

Registering and releasing resources

allocateEff Source #

Arguments

:: Resource :> es 
=> Eff es a

allocate

-> (a -> Eff es ())

free resource

-> Eff es (ReleaseKey, a) 

A variant of allocate adjusted to work in the Eff monad.

Note: the release action will run a cloned environment, so any changes it makes to thread local data will not be visible outside of it.

allocateEff_ Source #

Arguments

:: Resource :> es 
=> Eff es a

allocate

-> Eff es ()

free resource

-> Eff es ReleaseKey 

A variant of allocate_ adjusted to work in the Eff monad.

Note: the release action will run a cloned environment, so any changes it makes to thread local data will not be visible outside of it.

registerEff :: Resource :> es => Eff es () -> Eff es ReleaseKey Source #

A variant of register adjusted to work in the Eff monad.

Note: the release action will run a cloned environment, so any changes it makes to thread local data will not be visible outside of it.

releaseEff :: Resource :> es => ReleaseKey -> Eff es () Source #

A variant of release adjusted to work in the Eff monad.

allocate #

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

allocate_ #

Arguments

:: MonadResource m 
=> IO a

allocate

-> IO ()

free resource

-> m ReleaseKey 

Perform some allocation where the return value is not required, and automatically register a cleanup action.

allocate_ is to allocate as bracket_ is to bracket

This is almost identical to calling the allocation and then registering the release action, but this properly handles masking of asynchronous exceptions.

Since: resourcet-1.2.4

register :: MonadResource m => IO () -> m ReleaseKey #

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 () #

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 ())) #

Unprotect resource from cleanup actions; this allows you to send resource into another resourcet process and reregister it there. It returns a release action that should be run in order to clean resource or Nothing in case if resource is already freed.

Since 0.4.5

newtype ReleaseAction Source #

Action for releasing a resource.

Constructors

ReleaseAction 

Fields

unprotectEff :: Resource :> es => ReleaseKey -> Eff es (Maybe ReleaseAction) Source #

A variant of unprotect adjusted to work in the Eff monad.

Note: if the resource was acquired using allocateEff, allocateEff_ or registerEff then the returned ReleaseAction will run in a clone of the environment it was registered in.

See the documentation of the aforementioned functions for more information.

Internal state

type InternalState = IORef ReleaseMap #

The internal state held by a ResourceT transformer.

Since 0.4.6

getInternalState :: Resource :> es => Eff es InternalState Source #

Get the InternalState of the current Resource effect.

runInternalState :: IOE :> es => InternalState -> Eff (Resource ': es) a -> Eff es a Source #

Run the Resource effect with existing InternalState.

Note: the InternalState will not be closed at the end.

createInternalState :: MonadIO m => m InternalState #

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 () #

Close an internal state created by createInternalState.

Since 0.4.9

Re-exports

data ReleaseKey #

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

data ResourceCleanupException #

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

Since: resourcet-1.1.11

Constructors

ResourceCleanupException 

Fields

Orphan instances

(IOE :> es, Resource :> es) => MonadResource (Eff es) Source # 
Instance details

Methods

liftResourceT :: ResourceT IO a -> Eff es a #