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

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

Data.ConnectionPool.Internal.Unix

Description

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.

Synopsis

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.

Instances

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 Source #

Connection pool for TCP clients.

Definition changed in version 0.1.3 and 0.2. Instances for Generic and Show introduced in version 0.2.

data ConnectionPool * UnixClient Source #

Connection pool for UNIX Socket clients.

Definition changed in version 0.1.3 and 0.2. Instances for Generic and Show introduced in version 0.2.

type Rep (ConnectionPool * TcpClient) # 
type Rep (ConnectionPool * TcpClient) = D1 (MetaData "ConnectionPool" "Data.ConnectionPool.Internal.TCP" "connection-pool-0.2.1-FnRFrUPenjkD5VjSuGxxKR" True) (C1 (MetaCons "TcpConnectionPool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConnectionPool HandlerParams Socket SockAddr))))
type Rep (ConnectionPool * UnixClient) # 
type Rep (ConnectionPool * UnixClient) = D1 (MetaData "ConnectionPool" "Data.ConnectionPool.Internal.Unix" "connection-pool-0.2.1-FnRFrUPenjkD5VjSuGxxKR" True) (C1 (MetaCons "UnixConnectionPool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConnectionPool HandlerParams Socket ()))))

data UnixClient Source #

Type tag used to specialize connection pool for UNIX Socket clients.

Instance for Generic introduced in version 0.2.

Instances

Generic UnixClient Source # 

Associated Types

type Rep UnixClient :: * -> * #

HasConnectionPool HandlerParams Socket () (ConnectionPool * UnixClient) Source #

Since version 0.2.

ConnectionPoolFor * UnixClient Source #

Defined using:

withConnection = withUnixClientConnection
destroyAllConnections = destroyAllUnixClientConnections

Since version 0.2.

Associated Types

type HandlerData UnixClient (protocol :: UnixClient) :: * Source #

Show (ConnectionPool * UnixClient) Source # 
Generic (ConnectionPool * UnixClient) Source # 
type Rep UnixClient Source # 
type Rep UnixClient = D1 (MetaData "UnixClient" "Data.ConnectionPool.Internal.Unix" "connection-pool-0.2.1-FnRFrUPenjkD5VjSuGxxKR" False) V1
data ConnectionPool * UnixClient Source #

Connection pool for UNIX Socket clients.

Definition changed in version 0.1.3 and 0.2. Instances for Generic and Show introduced in version 0.2.

type HandlerData * UnixClient Source # 
type Rep (ConnectionPool * UnixClient) Source # 
type Rep (ConnectionPool * UnixClient) = D1 (MetaData "ConnectionPool" "Data.ConnectionPool.Internal.Unix" "connection-pool-0.2.1-FnRFrUPenjkD5VjSuGxxKR" True) (C1 (MetaCons "UnixConnectionPool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConnectionPool HandlerParams Socket ()))))

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.