connection-pool-0.2.1: Connection pool built on top of resource-pool and streaming-commons.

Copyright(c) 2014 Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityunstable (internal module)
PortabilityGHC specific language extensions.
Safe HaskellSafe
LanguageHaskell2010

Data.ConnectionPool.Internal.ResourcePoolParams

Contents

Description

Internal packages are here to provide access to internal definitions for library writers, but they should not be used in application code.

Preferably use qualified import, e.g.:

import qualified Data.ConnectionPool.Internal.ResourcePoolParams
  as Internal

Surprisingly this module doesn't depend on resource-pool package and it would be good if it stayed that way, but not at the cost of crippling functionality.

Importantly this package should not depend on streaming-commons package or other modules of this package.

Please, bear above in mind when doing modifications.

Synopsis

ResourcePoolParams

data ResourcePoolParams Source #

Parameters of resource pool that describe things like its internal structure. See createPool for details.

Instance for Generic introduced in version 0.2.

Instances

Data ResourcePoolParams Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourcePoolParams -> c ResourcePoolParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourcePoolParams #

toConstr :: ResourcePoolParams -> Constr #

dataTypeOf :: ResourcePoolParams -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourcePoolParams) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourcePoolParams) #

gmapT :: (forall b. Data b => b -> b) -> ResourcePoolParams -> ResourcePoolParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourcePoolParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourcePoolParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourcePoolParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourcePoolParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourcePoolParams -> m ResourcePoolParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourcePoolParams -> m ResourcePoolParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourcePoolParams -> m ResourcePoolParams #

Show ResourcePoolParams Source # 
Generic ResourcePoolParams Source # 
Default ResourcePoolParams Source #
numberOfStripes = 1
resourceIdleTimeout = 0.5
numberOfResourcesPerStripe = 1
type Rep ResourcePoolParams Source # 
type Rep ResourcePoolParams = D1 (MetaData "ResourcePoolParams" "Data.ConnectionPool.Internal.ResourcePoolParams" "connection-pool-0.2.1-CBLA23bwktW3txVQVHUtSC" False) (C1 (MetaCons "ResourcePoolParams" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_numberOfStripes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "_resourceIdleTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NominalDiffTime)) (S1 (MetaSel (Just Symbol "_numberOfResourcesPerStripe") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))

Lenses

numberOfResourcesPerStripe :: Functor f => (Int -> f Int) -> ResourcePoolParams -> f ResourcePoolParams Source #

Lens for accessing maximum number of resources to keep open per stripe. The smallest acceptable value is 1 (default).

numberOfStripes :: Functor f => (Int -> f Int) -> ResourcePoolParams -> f ResourcePoolParams Source #

Lens for accessing stripe count. The number of distinct sub-pools to maintain. The smallest acceptable value is 1 (default).

resourceIdleTimeout :: Functor f => (NominalDiffTime -> f NominalDiffTime) -> ResourcePoolParams -> f ResourcePoolParams Source #

Lens for accessing amount of time for which an unused resource is kept open. The smallest acceptable value is 0.5 seconds (default).

Validation

validateResourcePoolParams Source #

Arguments

:: ResourcePoolParams

Parameters to validate.

-> Either String ResourcePoolParams

Either error message or the same value of ResourcePoolParams passed as a first argument.

Check if all parameters for underlying resource pool are valid:

For more details see createPool.

Since version 0.1.1.0.