Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Resource management via MonadResource
.
Synopsis
- data Resource :: Effect
- runResource :: IOE :> es => Eff (Resource ': es) a -> Eff es a
- allocateEff :: Resource :> es => Eff es a -> (a -> Eff es ()) -> Eff es (ReleaseKey, a)
- allocateEff_ :: Resource :> es => Eff es a -> Eff es () -> Eff es ReleaseKey
- registerEff :: Resource :> es => Eff es () -> Eff es ReleaseKey
- releaseEff :: Resource :> es => ReleaseKey -> Eff es ()
- allocate :: MonadResource m => IO a -> (a -> IO ()) -> m (ReleaseKey, a)
- allocate_ :: MonadResource m => IO a -> IO () -> m ReleaseKey
- register :: MonadResource m => IO () -> m ReleaseKey
- release :: MonadIO m => ReleaseKey -> m ()
- unprotect :: MonadIO m => ReleaseKey -> m (Maybe (IO ()))
- newtype ReleaseAction = ReleaseAction {
- runReleaseAction :: forall es. Resource :> es => Eff es ()
- unprotectEff :: Resource :> es => ReleaseKey -> Eff es (Maybe ReleaseAction)
- type InternalState = IORef ReleaseMap
- getInternalState :: Resource :> es => Eff es InternalState
- runInternalState :: IOE :> es => InternalState -> Eff (Resource ': es) a -> Eff es a
- createInternalState :: MonadIO m => m InternalState
- closeInternalState :: MonadIO m => InternalState -> m ()
- data ReleaseKey
- data ResourceCleanupException = ResourceCleanupException {}
Effect
data Resource :: Effect Source #
Provide the ability to use the MonadResource
instance of Eff
.
Instances
type DispatchOf Resource Source # | |
Defined in Effectful.Resource | |
newtype StaticRep Resource Source # | |
Defined in Effectful.Resource |
Handlers
Registering and releasing resources
registerEff :: Resource :> es => Eff es () -> Eff es ReleaseKey Source #
releaseEff :: Resource :> es => ReleaseKey -> Eff es () Source #
:: 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
register
ing the release action, but this properly handles masking of
asynchronous exceptions.
Since 0.3.0
:: 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
register
ing 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.
ReleaseAction | |
|
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
ResourceCleanupException | |
|