Safe Haskell | None |
---|---|
Language | Haskell2010 |
This was previously known as the Resource monad. However, that term is confusing next to the ResourceT transformer, so it has been renamed.
Synopsis
- data Acquire a
- with :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b
- withAcquire :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b
- mkAcquire :: IO a -> (a -> IO ()) -> Acquire a
- mkAcquireType :: IO a -> (a -> ReleaseType -> IO ()) -> Acquire a
- allocateAcquire :: MonadResource m => Acquire a -> m ( ReleaseKey , a)
- data ReleaseType
Documentation
A method for acquiring a scarce resource, providing the means of freeing
it when no longer needed. This data type provides
Functor
/
Applicative
/
Monad
instances for composing different resources
together. You can allocate these resources using either the
bracket
pattern (via
with
) or using
ResourceT
(via
allocateAcquire
).
This concept was originally introduced by Gabriel Gonzalez and described at: http://www.haskellforall.com/2013/06/the-resource-applicative.html . The implementation in this package is slightly different, due to taking a different approach to async exception safety.
Since: 1.1.0
Example usage of
Acquire
for allocating a resource and freeing it up.
The code makes use of
mkAcquire
to create an
Acquire
and uses
allocateAcquire
to allocate the resource and register an action to free up the resource.
Reproducible Stack code snippet
#!/usr/bin/env stack {- stack --resolver lts-10.0 --install-ghc runghc --package resourcet -} {-#LANGUAGE ScopedTypeVariables#-} import Data.Acquire import Control.Monad.Trans.Resource import Control.Monad.IO.Class main :: IO () main = runResourceT $ do let (ack :: Acquire Int) = mkAcquire (do putStrLn "Enter some number" readLn) (\i -> putStrLn $ "Freeing scarce resource: " ++ show i) (releaseKey, resource) <- allocateAcquire ack doSomethingDangerous resource liftIO $ putStrLn $ "Going to release resource immediately: " ++ show resource release releaseKey somethingElse doSomethingDangerous :: Int -> ResourceT IO () doSomethingDangerous i = liftIO $ putStrLn $ "5 divided by " ++ show i ++ " is " ++ show (5 `div` i) somethingElse :: ResourceT IO () somethingElse = liftIO $ putStrLn "This could take a long time, don't delay releasing the resource!"
Execution output:
~ $ stack code.hs Enter some number 3 5 divided by 3 is 1 Going to release resource immediately: 3 Freeing scarce resource: 3 This could take a long time, don't delay releasing the resource! ~ $ stack code.hs Enter some number 0 5 divided by 0 is Freeing scarce resource: 0 code.hs: divide by zero
with :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b Source #
Allocate the given resource and provide it to the provided function. The
resource will be freed as soon as the inner block is exited, whether
normally or via an exception. This function is similar in function to
bracket
.
Since: 1.1.0
withAcquire :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b Source #
Longer name for
with
, in case
with
is not obvious enough in context.
Since: 1.2.0
Create an
Acquire
value using the given allocate and free functions.
To acquire and free the resource in an arbitrary monad with
MonadUnliftIO
,
do the following:
acquire <- withRunInIO $ \runInIO -> return $ mkAcquire (runInIO create) (runInIO . free)
Note that this is only safe if the Acquire is run and freed within the same monadic scope it was created in.
Since: 1.1.0
:: IO a |
acquire the resource |
-> (a -> ReleaseType -> IO ()) |
free the resource |
-> Acquire a |
Same as
mkAcquire
, but the cleanup function will be informed of
how
cleanup was initiated. This allows you to distinguish, for example, between
normal and exceptional exits.
To acquire and free the resource in an arbitrary monad with
MonadUnliftIO
,
do the following:
acquire <- withRunInIO $ \runInIO -> return $ mkAcquireType (runInIO create) (\a -> runInIO . free a)
Note that this is only safe if the Acquire is run and freed within the same monadic scope it was created in.
Since: 1.1.2
allocateAcquire :: MonadResource m => Acquire a -> m ( ReleaseKey , a) Source #
Allocate a resource and register an action with the
MonadResource
to
free the resource.
Since: 1.1.0
data ReleaseType Source #
The way in which a release is called.
Since: 1.1.2