Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Pool.Internal
Description
Internal implementation details for Data.Pool.
This module is intended for internal use only, and may change without warning in subsequent releases.
Synopsis
- data Pool a = Pool {
- poolConfig :: !(PoolConfig a)
- localPools :: !(SmallArray (LocalPool a))
- reaperRef :: !(IORef ())
- data LocalPool a = LocalPool {}
- data Stripe a = Stripe {}
- data Entry a = Entry {}
- data Queue a
- data PoolConfig a = PoolConfig {
- createResource :: !(IO a)
- freeResource :: !(a -> IO ())
- poolCacheTTL :: !Double
- poolMaxResources :: !Int
- poolNumStripes :: !(Maybe Int)
- pcLabel :: !Text
- defaultPoolConfig :: IO a -> (a -> IO ()) -> Double -> Int -> PoolConfig a
- setNumStripes :: Maybe Int -> PoolConfig a -> PoolConfig a
- setPoolLabel :: Text -> PoolConfig a -> PoolConfig a
- newPool :: PoolConfig a -> IO (Pool a)
- destroyResource :: Pool a -> LocalPool a -> a -> IO ()
- putResource :: LocalPool a -> a -> IO ()
- destroyAllResources :: Pool a -> IO ()
- getLocalPool :: SmallArray (LocalPool a) -> IO (LocalPool a)
- waitForResource :: TVar (Stripe a) -> TMVar (Maybe a) -> IO (Maybe a)
- restoreSize :: TVar (Stripe a) -> IO ()
- cleanStripe :: (Entry a -> Bool) -> (a -> IO ()) -> TVar (Stripe a) -> IO ()
- signal :: Stripe a -> Maybe a -> STM (Stripe a)
Documentation
Striped resource pool based on Control.Concurrent.QSem.
Constructors
Pool | |
Fields
|
A single, local pool.
Stripe of a resource pool. If available
is 0, the list of threads waiting
for a resource (each with an associated TMVar
) is queue ++ reverse queueR
to ensure fairness.
An existing resource currently sitting in a pool.
A queue of TMVarS corresponding to threads waiting for resources.
Basically a monomorphic list to save two pointer indirections.
data PoolConfig a Source #
Configuration of a Pool
.
Constructors
PoolConfig | |
Fields
|
Arguments
:: IO a | The action that creates a new resource. |
-> (a -> IO ()) | The action that destroys an existing resource. |
-> Double | The number of seconds for which an unused resource is kept around. The
smallest acceptable value is Note: the elapsed time before destroying a resource may be a little longer than requested, as the collector thread wakes at 1-second intervals. |
-> Int | The maximum number of resources to keep open across all stripes. The
smallest acceptable value is Note: if the number of stripes does not divide the number of resources, some of the stripes will have 1 more resource available than the others. |
-> PoolConfig a |
Create a PoolConfig
with optional parameters having default values.
For setting optional parameters have a look at:
Since: 0.4.0.0
setNumStripes :: Maybe Int -> PoolConfig a -> PoolConfig a Source #
Set the number of stripes (sub-pools) in the pool.
If not explicitly set, the default number of stripes is 1, which should be good for typical use (when in doubt, profile your application first).
If set to Nothing
, the pool will create the number of stripes equal to the
number of capabilities.
Note: usage of multiple stripes reduces contention, but can also result in suboptimal use of resources since stripes are separated from each other.
Since: 0.4.0.0
setPoolLabel :: Text -> PoolConfig a -> PoolConfig a Source #
Assign a label to the pool.
The label will appear in a label of the collector thread as well as
Resource
.
Since: 0.5.0.0
newPool :: PoolConfig a -> IO (Pool a) Source #
Create a new striped resource pool.
Note: although the runtime system will destroy all idle resources when the
pool is garbage collected, it's recommended to manually call
destroyAllResources
when you're done with the pool so that the resources
are freed up as soon as possible.
destroyResource :: Pool a -> LocalPool a -> a -> IO () Source #
Destroy a resource.
Note that this will ignore any exceptions in the destroy function.
destroyAllResources :: Pool a -> IO () Source #
Destroy all resources in all stripes in the pool.
Note that this will ignore any exceptions in the destroy function.
This function is useful when you detect that all resources in the pool are
broken. For example after a database has been restarted all connections
opened before the restart will be broken. In that case it's better to close
those connections so that takeResource
won't take a broken connection from
the pool but will open a new connection instead.
Another use-case for this function is that when you know you are done with the pool you can destroy all idle resources immediately instead of waiting on the garbage collector to destroy them, thus freeing up those resources sooner.
getLocalPool :: SmallArray (LocalPool a) -> IO (LocalPool a) Source #
Get a local pool.
waitForResource :: TVar (Stripe a) -> TMVar (Maybe a) -> IO (Maybe a) Source #
Wait for the resource to be put into a given TMVar
.
restoreSize :: TVar (Stripe a) -> IO () Source #
If an exception is received while a resource is being created, restore the original size of the stripe.