Copyright | (c) 2014-2015, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | unstable (internal module) |
Portability | CPP, DeriveDataTypeable, DeriveGeneric, FlexibleInstances, MultiParamTypeClasses, NoImplicitPrelude, PolyKinds, StandaloneDeriving, TupleSections, TypeFamilies |
Safe Haskell | None |
Language | Haskell2010 |
Module defines type family of connection pools that is later specialised
using type tags (phantom types) to specialize implementation of underlying
ConnectionPool
for various protocols.
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.Unix as Internal
This package is OS specific, because Windows doesn't support UNIX Sockets. Please, bear this in mind when doing modifications.
Module introduced in version 0.2.
- data family ConnectionPool :: k -> *
- data UnixClient
- createUnixClientPool :: ResourcePoolParams -> ClientSettingsUnix -> IO (ConnectionPool UnixClient)
- withUnixClientConnection :: (MonadBaseControl io m, io ~ IO) => ConnectionPool UnixClient -> (AppDataUnix -> m r) -> m r
- tryWithUnixClientConnection :: (MonadBaseControl io m, io ~ IO) => ConnectionPool UnixClient -> (AppDataUnix -> m r) -> m (Maybe r)
- destroyAllUnixClientConnections :: ConnectionPool UnixClient -> IO ()
Documentation
data family ConnectionPool :: k -> * Source
Family of connection pools parametrised by transport protocol.
Definition changed version 0.2 to be kind polymorphic (only on GHC >= 7.10) and became part of stable API by being moved in to Data.ConnectionPool.Family module.
HasConnectionPool HandlerParams Socket () (ConnectionPool * UnixClient) Source | Since version 0.2. |
HasConnectionPool HandlerParams Socket SockAddr (ConnectionPool * TcpClient) Source | Since version 0.2. |
Show (ConnectionPool * TcpClient) | |
Show (ConnectionPool * UnixClient) | |
Generic (ConnectionPool * TcpClient) | |
Generic (ConnectionPool * UnixClient) | |
data ConnectionPool * TcpClient = TcpConnectionPool (ConnectionPool HandlerParams Socket SockAddr) Source | Connection pool for TCP clients. Definition changed in version 0.1.3 and 0.2.
Instances for |
data ConnectionPool * UnixClient = UnixConnectionPool (ConnectionPool HandlerParams Socket ()) Source | Connection pool for UNIX Socket clients. Definition changed in version 0.1.3 and 0.2.
Instances for |
type Rep (ConnectionPool * TcpClient) | |
type Rep (ConnectionPool * UnixClient) |
data UnixClient Source
Type tag used to specialize connection pool for UNIX Socket clients.
Instance for Generic
introduced in version 0.2.
Generic UnixClient Source | |
ConnectionPoolFor * UnixClient Source | Defined using:
Since version 0.2. |
HasConnectionPool HandlerParams Socket () (ConnectionPool * UnixClient) Source | Since version 0.2. |
Show (ConnectionPool * UnixClient) Source | |
Generic (ConnectionPool * UnixClient) Source | |
type Rep UnixClient Source | |
data ConnectionPool * UnixClient = UnixConnectionPool (ConnectionPool HandlerParams Socket ()) Source | Connection pool for UNIX Socket clients. Definition changed in version 0.1.3 and 0.2.
Instances for |
type HandlerData * UnixClient = AppDataUnix Source | |
type Rep (ConnectionPool * UnixClient) Source |
createUnixClientPool :: ResourcePoolParams -> ClientSettingsUnix -> IO (ConnectionPool UnixClient) Source
Create connection pool for UNIX Sockets clients.
withUnixClientConnection :: (MonadBaseControl io m, io ~ IO) => ConnectionPool UnixClient -> (AppDataUnix -> m r) -> m r Source
Temporarily take a UNIX Sockets connection from a pool, run client with
it, and return it to the pool afterwards. For details how connections are
allocated see withResource
.
tryWithUnixClientConnection :: (MonadBaseControl io m, io ~ IO) => ConnectionPool UnixClient -> (AppDataUnix -> m r) -> m (Maybe r) Source
Similar to withConnection
, but only performs action if a UNIX Sockets
connection could be taken from the pool without blocking. Otherwise,
tryWithResource
returns immediately with Nothing
(ie. the action
function is not called). Conversely, if a connection can be acquired from
the pool without blocking, the action is performed and it's result is
returned, wrapped in a Just
.
Since version 0.2.
destroyAllUnixClientConnections :: ConnectionPool UnixClient -> IO () Source
Destroy all UNIX Sockets 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.