resource-pool-0.5.0.0: A high-performance striped resource pooling implementation
Safe HaskellNone
LanguageHaskell2010

Data.Pool.Introspection

Description

A variant of Data.Pool with introspection capabilities.

Synopsis

Pool

data Pool a Source #

Striped resource pool based on Control.Concurrent.QSem.

data LocalPool a Source #

A single, local pool.

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.

Configuration

data PoolConfig a Source #

Configuration of a Pool.

defaultPoolConfig Source #

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 0.5.

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 1 per stripe.

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

Resource management

data Resource a Source #

A resource taken from the pool along with additional information.

Instances

Instances details
Generic (Resource a) Source # 
Instance details

Defined in Data.Pool.Introspection

Associated Types

type Rep (Resource a) 
Instance details

Defined in Data.Pool.Introspection

type Rep (Resource a) = D1 ('MetaData "Resource" "Data.Pool.Introspection" "resource-pool-0.5.0.0-FUFyxkagWyaLVOj0ksZc21" 'False) (C1 ('MetaCons "Resource" 'PrefixI 'True) ((S1 ('MetaSel ('Just "resource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "poolLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "stripeNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "availableResources") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "acquisition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Acquisition)) :*: (S1 ('MetaSel ('Just "acquisitionTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "creationTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Double))))))

Methods

from :: Resource a -> Rep (Resource a) x #

to :: Rep (Resource a) x -> Resource a #

Show a => Show (Resource a) Source # 
Instance details

Defined in Data.Pool.Introspection

Methods

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

show :: Resource a -> String #

showList :: [Resource a] -> ShowS #

Eq a => Eq (Resource a) Source # 
Instance details

Defined in Data.Pool.Introspection

Methods

(==) :: Resource a -> Resource a -> Bool #

(/=) :: Resource a -> Resource a -> Bool #

type Rep (Resource a) Source # 
Instance details

Defined in Data.Pool.Introspection

type Rep (Resource a) = D1 ('MetaData "Resource" "Data.Pool.Introspection" "resource-pool-0.5.0.0-FUFyxkagWyaLVOj0ksZc21" 'False) (C1 ('MetaCons "Resource" 'PrefixI 'True) ((S1 ('MetaSel ('Just "resource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "poolLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "stripeNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "availableResources") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "acquisition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Acquisition)) :*: (S1 ('MetaSel ('Just "acquisitionTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "creationTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Double))))))

data Acquisition Source #

Describes how a resource was acquired from the pool.

Constructors

Immediate

A resource was taken from the pool immediately.

Delayed

The thread had to wait until a resource was released.

Instances

Instances details
Generic Acquisition Source # 
Instance details

Defined in Data.Pool.Introspection

Associated Types

type Rep Acquisition 
Instance details

Defined in Data.Pool.Introspection

type Rep Acquisition = D1 ('MetaData "Acquisition" "Data.Pool.Introspection" "resource-pool-0.5.0.0-FUFyxkagWyaLVOj0ksZc21" 'False) (C1 ('MetaCons "Immediate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Delayed" 'PrefixI 'False) (U1 :: Type -> Type))
Show Acquisition Source # 
Instance details

Defined in Data.Pool.Introspection

Eq Acquisition Source # 
Instance details

Defined in Data.Pool.Introspection

type Rep Acquisition Source # 
Instance details

Defined in Data.Pool.Introspection

type Rep Acquisition = D1 ('MetaData "Acquisition" "Data.Pool.Introspection" "resource-pool-0.5.0.0-FUFyxkagWyaLVOj0ksZc21" 'False) (C1 ('MetaCons "Immediate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Delayed" 'PrefixI 'False) (U1 :: Type -> Type))

withResource :: Pool a -> (Resource a -> IO r) -> IO r Source #

withResource with introspection capabilities.

takeResource :: Pool a -> IO (Resource a, LocalPool a) Source #

takeResource with introspection capabilities.

tryWithResource :: Pool a -> (Resource a -> IO r) -> IO (Maybe r) Source #

A variant of withResource that doesn't execute the action and returns Nothing instead of blocking if the local pool is exhausted.

tryTakeResource :: Pool a -> IO (Maybe (Resource a, LocalPool a)) Source #

A variant of takeResource that returns Nothing instead of blocking if the local pool is exhausted.

putResource :: LocalPool a -> a -> IO () Source #

Return a resource to the given LocalPool.

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.