lazy-bracket-0.1.0.0: A bracket with lazy resource allocation.
Safe HaskellSafe-Inferred
LanguageHaskell2010

LazyBracket

Description

This module provides variants of the bracket function that delay the acquisition of the resource until it's used for the first time. If the resource is never used, it will never be acquired.

A trivial example. This bracket code with a faulty acquisition doesn't throw an exception because the resource is never accessed:

>>> :{
 lazyBracket 
   (throwIO (userError "oops")) 
   (\_ -> pure ()) 
   \Resource {} -> do 
     pure () 
:}

But this code does:

>>> :{
 lazyBracket 
   (throwIO (userError "oops")) 
   (\_ -> pure ()) 
   \Resource {accessResource} -> do 
     _ <- accessResource
     pure () 
:}
*** Exception: user error (oops)

To be even more lazy, certain kinds of operations on the resource do not trigger acquisition: instead, they are stashed and applied once the resource has been acquired for other reasons.

Look at the sequence of ouput messages here:

>>> :{
 lazyBracket 
   (putStrLn "acquired!") 
   (\() -> putStrLn "released!") 
   \Resource {accessResource, controlResource} -> do 
     controlResource \() -> putStrLn "control op 1 - delayed"
     putStrLn "before acquiring"
     _ <- accessResource
     putStrLn "after acquiring"
     controlResource \() -> putStrLn "control op 2 - immediately executed"
     pure () 
:}
before acquiring
acquired!
control op 1 - delayed
after acquiring
control op 2 - immediately executed
released!

If we never access the resource, the release function and the stashed operations are not executed:

>>> :{
 lazyBracket 
   (putStrLn "acquired!") 
   (\() -> putStrLn "released!") 
   \Resource {accessResource, controlResource} -> do 
     controlResource \() -> putStrLn "control op 1 - never happens"
     pure () 
:}
Synopsis

Lazy brackets that delay resource acquisition.

lazyBracket Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> IO a

Computation to run to acquire the resource.

-> (a -> m c)

Computation to run to release the resource, in case it was acquired.

-> (Resource a -> m b)

Computation to run in-between (might trigger resource acquisition).

-> m b

Returns the value from the in-between computation

A version of bracket for which the resource is not acquired at the beginning, but the first time it's used in the main callback. If the resource is never used, it won't be acquired.

lazyGeneralBracket Source #

Arguments

:: forall m a b c. (MonadIO m, MonadMask m) 
=> IO a

Computation to run to acquire the resource

-> (a -> ExitCase b -> m c)

Computation to run to release the resource, in case it was acquired

The release function has knowledge of how the main callback was exited: by normal completion, by a runtime exception, or otherwise aborted. This can be useful when acquiring resources from resource pools, to decide whether to return the resource to the pool or to destroy it.

-> (Resource a -> m b)

Computation to run in-between (might trigger resource acquisition)

-> m (b, Maybe c)

Returns the value from the in-between computation, and also of the release computation, if it took place.

A version of generalBracket for which the resource is not acquired at the beginning, but the first time it's used in the main callback. If the resource is never used, it won't be acquired.

lazyGeneralBracket_ Source #

Arguments

:: forall m a b c. (MonadIO m, MonadMask m) 
=> IO a

computation to run to acquire the resource

-> (a -> ExitCase b -> m c)

computation to run to release the resource, in case it was acquired

-> (Resource a -> m b)

computation to run in-between (might trigger resource acquisition)

-> m b

returns the value from the in-between computation.

Slightly simpler version of lazyGeneralBracket that doesn't return the result of the release computation.

Resource wrapper.

data Resource a Source #

A wrapper type over resources that delays resource acquisition.

Because one must be careful with the kinds of functions that are passed to controlResource, it might be a good idea to define convenience wrappers over Resource with more restricted interfaces.

Constructors

Resource 

Fields

  • accessResource :: IO a

    Action to get hold of the resource. Will trigger resource acquisition and apply all stashed control operations the first time it's run.

  • controlResource :: (a -> IO ()) -> IO ()

    Immediately apply a "control" operation to the underlying resource if the resource has already been acquired, otherwise stash the operation with the intention of applying it once the resource is eventually acquired. If the resource is never acquired, stashed operations are discarded.

    By "control" operations we mean operations that are not essential in and of themselves, only serve to modify the behaviour of operations that are actually essential, and can be omitted if no essential operations take place.

    Some examples:

    For file handle resources, hSetBuffering is a valid control operation, whereas actually writing bytes to the handle is not.

    For database connection resources, beginning a transaction is a valid control operation, whereas performing an INSERT is not.

Re-exports.

data ExitCase a #

A MonadMask computation may either succeed with a value, abort with an exception, or abort for some other reason. For example, in ExceptT e IO you can use throwM to abort with an exception (ExitCaseException) or throwE to abort with a value of type e (ExitCaseAbort).

Instances

Instances details
Show a => Show (ExitCase a) 
Instance details

Defined in Control.Monad.Catch

Methods

showsPrec :: Int -> ExitCase a -> ShowS #

show :: ExitCase a -> String #

showList :: [ExitCase a] -> ShowS #