Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A variant of Data.Pool with introspection capabilities.
Synopsis
- data Pool a
- data LocalPool a
- newPool :: PoolConfig a -> IO (Pool a)
- data PoolConfig a
- defaultPoolConfig :: IO a -> (a -> IO ()) -> Double -> Int -> PoolConfig a
- setNumStripes :: Maybe Int -> PoolConfig a -> PoolConfig a
- data Resource a = Resource {
- resource :: a
- stripeNumber :: !Int
- availableResources :: !Int
- acquisition :: !Acquisition
- acquisitionTime :: !Double
- creationTime :: !(Maybe Double)
- data Acquisition
- withResource :: Pool a -> (Resource a -> IO r) -> IO r
- takeResource :: Pool a -> IO (Resource a, LocalPool a)
- tryWithResource :: Pool a -> (Resource a -> IO r) -> IO (Maybe r)
- tryTakeResource :: Pool a -> IO (Maybe (Resource a, LocalPool a))
- putResource :: LocalPool a -> a -> IO ()
- destroyResource :: Pool a -> LocalPool a -> a -> IO ()
- destroyAllResources :: Pool a -> IO ()
Pool
Striped resource pool based on Control.Concurrent.QSem.
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
.
:: IO a | The action that creates a new resource. |
-> (a -> IO ()) | The action that destroys an existing resource. |
-> Double | The amount 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: for each stripe the number of resources is divided by the number of
stripes and rounded up, hence the pool might end up creating up to |
-> 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 in the pool.
If set to Nothing
(the default value), the pool will create the amount of
stripes equal to the number of capabilities. This ensures that threads never
compete over access to the same stripe and results in a very good performance
in a multi-threaded environment.
Since: 0.4.0.0
Resource management
A resource taken from the pool along with additional information.
Resource | |
|
Instances
Generic (Resource a) Source # | |
Show a => Show (Resource a) Source # | |
Eq a => Eq (Resource a) Source # | |
type Rep (Resource a) Source # | |
Defined in Data.Pool.Introspection type Rep (Resource a) = D1 ('MetaData "Resource" "Data.Pool.Introspection" "resource-pool-0.4.0.0-5FNzHrdfAAD5PLcv845Nvu" 'False) (C1 ('MetaCons "Resource" 'PrefixI 'True) ((S1 ('MetaSel ('Just "resource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (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.
Immediate | A resource was taken from the pool immediately. |
Delayed | The thread had to wait until a resource was released. |
Instances
Generic Acquisition Source # | |
Defined in Data.Pool.Introspection type Rep Acquisition :: Type -> Type # from :: Acquisition -> Rep Acquisition x # to :: Rep Acquisition x -> Acquisition # | |
Show Acquisition Source # | |
Defined in Data.Pool.Introspection showsPrec :: Int -> Acquisition -> ShowS # show :: Acquisition -> String # showList :: [Acquisition] -> ShowS # | |
Eq Acquisition Source # | |
Defined in Data.Pool.Introspection (==) :: Acquisition -> Acquisition -> Bool # (/=) :: Acquisition -> Acquisition -> Bool # | |
type Rep Acquisition Source # | |
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.
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.