Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data InvalidAccess = InvalidAccess {}
- class MonadIO m => MonadResource m where
- data ReleaseKey = ReleaseKey !(IORef ReleaseMap) !Int
- data ReleaseMap
- = ReleaseMap !NextKey !RefCount !(IntMap (ReleaseType -> IO ()))
- | ReleaseMapClosed
- type ResIO = ResourceT IO
- newtype ResourceT m a = ResourceT {
- unResourceT :: IORef ReleaseMap -> m a
- stateAlloc :: IORef ReleaseMap -> IO ()
- stateCleanup :: ReleaseType -> IORef ReleaseMap -> IO ()
- transResourceT :: (m a -> n b) -> ResourceT m a -> ResourceT n b
- register' :: IORef ReleaseMap -> IO () -> IO ReleaseKey
- registerType :: IORef ReleaseMap -> (ReleaseType -> IO ()) -> IO ReleaseKey
- data ResourceCleanupException = ResourceCleanupException {}
- stateCleanupChecked :: Maybe SomeException -> IORef ReleaseMap -> IO ()
Documentation
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
Instances
Show InvalidAccess Source # | |
Defined in Control.Monad.Trans.Resource.Internal showsPrec :: Int -> InvalidAccess -> ShowS # show :: InvalidAccess -> String # showList :: [InvalidAccess] -> ShowS # | |
Exception InvalidAccess Source # | |
Defined in Control.Monad.Trans.Resource.Internal |
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
liftResourceT :: ResourceT IO a -> m a Source #
Lift a ResourceT IO
action into the current Monad
.
Since 0.4.0
Instances
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
ReleaseKey !(IORef ReleaseMap) !Int |
data ReleaseMap Source #
ReleaseMap !NextKey !RefCount !(IntMap (ReleaseType -> IO ())) | |
ReleaseMapClosed |
newtype 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
ResourceT | |
|
Instances
stateAlloc :: IORef ReleaseMap -> IO () Source #
stateCleanup :: ReleaseType -> IORef ReleaseMap -> IO () Source #
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
register' :: IORef ReleaseMap -> IO () -> IO ReleaseKey Source #
registerType :: IORef ReleaseMap -> (ReleaseType -> IO ()) -> IO ReleaseKey Source #
Since 1.1.2
data ResourceCleanupException Source #
Thrown when one or more cleanup functions themselves throw an exception during cleanup.
Since: resourcet-1.1.11
ResourceCleanupException | |
|
Instances
:: Maybe SomeException | exception that killed the |
-> IORef ReleaseMap | |
-> IO () |
Clean up a release map, but throw a ResourceCleanupException
if
anything goes wrong in the cleanup handlers.
Since: resourcet-1.1.11