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

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

Data.ConnectionPool.Internal.ConnectionPool

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.ConnectionPool as Internal

This module doesn't depend on streaming-commons and other non-HaskellPlatform packages with exception of two packages resource-pool and between. Another notable thing is that this package is not OS specific. Please, bear this in mind when doing modifications.

Synopsis

Data Type For Building Connection Pools

data ConnectionPool handlerParams connection connectionInfo Source #

Simple specialized wrapper for Pool.

Definition changed in version 0.1.3 and 0.2. Instance for Generic introduced in version 0.2.

Constructors

ConnectionPool 

Fields

Instances

Show handlerParams => Show (ConnectionPool handlerParams c i) Source #

Since version 0.1.3.

Methods

showsPrec :: Int -> ConnectionPool handlerParams c i -> ShowS #

show :: ConnectionPool handlerParams c i -> String #

showList :: [ConnectionPool handlerParams c i] -> ShowS #

Generic (ConnectionPool handlerParams connection connectionInfo) Source # 

Associated Types

type Rep (ConnectionPool handlerParams connection connectionInfo) :: * -> * #

Methods

from :: ConnectionPool handlerParams connection connectionInfo -> Rep (ConnectionPool handlerParams connection connectionInfo) x #

to :: Rep (ConnectionPool handlerParams connection connectionInfo) x -> ConnectionPool handlerParams connection connectionInfo #

type Rep (ConnectionPool handlerParams connection connectionInfo) Source # 
type Rep (ConnectionPool handlerParams connection connectionInfo) = D1 * (MetaData "ConnectionPool" "Data.ConnectionPool.Internal.ConnectionPool" "connection-pool-0.2.2-6QO2HFAP66s57rNsrMe34b" False) (C1 * (MetaCons "ConnectionPool" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_resourcePool") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Pool (connection, connectionInfo)))) (S1 * (MetaSel (Just Symbol "_handlerParams") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * handlerParams))))

Lenses

resourcePool :: Functor f => (Pool (c, i) -> f (Pool (c', i'))) -> ConnectionPool p c i -> f (ConnectionPool p c' i') Source #

Lens for accessing underlying resource pool Pool (connection, connectionInfo). Where connection represents network connection and connectionInfo is a protocol specific information associated with the same network connection as the connection is.

Since version 0.1.3; changed in 0.2.

handlerParams :: Functor f => (handlerParams -> f handlerParams') -> ConnectionPool handlerParams c i -> f (ConnectionPool handlerParams' c i) Source #

Lens for accessing parameters passed down to connection handler. These information will usually be implementation specific. E.g. for streaming-commons >= 1.13 we use this to pass around read buffer size, for more details see module Data.ConnectionPool.Internal.HandlerParams.

Since version 0.1.3.

Lifted Resource Pool Operations

Operations on Pool lifted to work on ConnectionPool data type.

createConnectionPool Source #

Arguments

:: handlerParams

Data type passed down to individual connection handlers.

Since version 0.1.3.

-> IO (connection, connectionInfo)

Acquire a connection which is represented by a connection. There might be additional information associated with specific connection that we pass as a sencond value in a tuple. Such information are considered read only and aren't passed to release function (see next argument).

Changed in version 0.2.

-> (connection -> IO ())

Release a connection which is represented by a connection.

Changed in version 0.2.

-> ResourcePoolParams

Data type representing all createPool parameters that describe internal Pool parameters.

-> IO (ConnectionPool handlerParams connection connectionInfo)

Created connection pool that is parametrised by additional connection details.

Specialized wrapper for createPool, see its documentation for details.

Definition changed in version 0.1.3 and version 0.2.

destroyAllConnections :: ConnectionPool p c i -> IO () Source #

Destroy all connections that might be still open in a connection pool. This is useful when one needs to release all resources at once and not to wait for idle timeout to be reached.

For more details see destroyAllResources.

Since version 0.1.1.0.

withConnection :: MonadBaseControl IO m => ConnectionPool handlerParams connection connectionInfo -> (handlerParams -> connection -> connectionInfo -> m r) -> m r Source #

Specialized wrapper for withResource.

Changed in version 0.2.

tryWithConnection :: MonadBaseControl IO m => ConnectionPool handlerParams connection connectionInfo -> (handlerParams -> connection -> connectionInfo -> m r) -> m (Maybe r) Source #

Specialized wrapper for tryWithResource.

Since version 0.2.