Copyright | (c) 2014-2015, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | unstable (internal module) |
Portability | DeriveDataTypeable, DeriveGeneric, FunctionalDependencies, FlexibleContexts, MultiParamTypeClasses, NamedFieldPuns, NoImplicitPrelude, RecordWildCards |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data ConnectionPool handlerParams connection connectionInfo = ConnectionPool {
- _resourcePool :: !(Pool (connection, connectionInfo))
- _handlerParams :: !handlerParams
- resourcePool :: Functor f => (Pool (c, i) -> f (Pool (c', i'))) -> ConnectionPool p c i -> f (ConnectionPool p c' i')
- handlerParams :: Functor f => (handlerParams -> f handlerParams') -> ConnectionPool handlerParams c i -> f (ConnectionPool handlerParams' c i)
- class HasConnectionPool p c i s | s -> p, s -> c, s -> i where
- connectionPool :: Functor f => (ConnectionPool p c i -> f (ConnectionPool p c i)) -> s -> f s
- createConnectionPool :: handlerParams -> IO (connection, connectionInfo) -> (connection -> IO ()) -> ResourcePoolParams -> IO (ConnectionPool handlerParams connection connectionInfo)
- destroyAllConnections :: ConnectionPool p c i -> IO ()
- withConnection :: MonadBaseControl IO m => ConnectionPool handlerParams connection connectionInfo -> (handlerParams -> connection -> connectionInfo -> m r) -> m r
- tryWithConnection :: MonadBaseControl IO m => ConnectionPool handlerParams connection connectionInfo -> (handlerParams -> connection -> connectionInfo -> m r) -> m (Maybe r)
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.
ConnectionPool | |
|
Show handlerParams => Show (ConnectionPool handlerParams c i) Source | Since version 0.1.3. |
Generic (ConnectionPool handlerParams connection connectionInfo) Source | |
type Rep (ConnectionPool handlerParams connection connectionInfo) Source |
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
. Where Pool
(connection,
connectionInfo)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.
class HasConnectionPool p c i s | s -> p, s -> c, s -> i where Source
Since version 0.2.
connectionPool :: Functor f => (ConnectionPool p c i -> f (ConnectionPool p c i)) -> s -> f s Source
Lens for accessing ConnectionPool
wrapped in a data type.
HasConnectionPool HandlerParams Socket () (ConnectionPool * UnixClient) Source | Since version 0.2. |
HasConnectionPool HandlerParams Socket SockAddr (ConnectionPool * TcpClient) Source | Since version 0.2. |
Lifted Resource Pool Operations
Operations on Pool
lifted to work on ConnectionPool
data type.
:: 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 Changed in version 0.2. |
-> (connection -> IO ()) | Release a connection which is represented by a Changed in version 0.2. |
-> ResourcePoolParams | Data type representing all |
-> 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.