#ifdef KIND_POLYMORPHIC_TYPEABLE
#endif
module Data.ConnectionPool.Internal.TCP
( ConnectionPool(..)
, TcpClient
, createTcpClientPool
, withTcpClientConnection
, tryWithTcpClientConnection
, destroyAllTcpClientConnections
)
where
import Data.Function ((.), const)
import Data.Functor ((<$>))
import Data.Maybe (Maybe(Nothing))
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Show (Show)
import System.IO (IO)
import Network.Socket (SockAddr, Socket)
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Function.Between.Strict ((<^@~))
import Data.Streaming.Network
( AppData
, ClientSettings
)
import Data.ConnectionPool.Class
( ConnectionPoolFor
( HandlerData
, destroyAllConnections
, tryWithConnection
, withConnection
)
)
import Data.ConnectionPool.Family (ConnectionPool)
import Data.ConnectionPool.Internal.ConnectionPool
( HasConnectionPool(connectionPool)
)
import qualified Data.ConnectionPool.Internal.ConnectionPool as Internal
( ConnectionPool
, createConnectionPool
, destroyAllConnections
, tryWithConnection
, withConnection
)
import Data.ConnectionPool.Internal.HandlerParams (HandlerParams)
import qualified Data.ConnectionPool.Internal.Streaming as Internal
( acquireTcpClientConnection
, close
, fromClientSettings
, runTcpApp
)
import Data.ConnectionPool.Internal.ResourcePoolParams (ResourcePoolParams)
data TcpClient
deriving (Generic, Typeable)
newtype instance ConnectionPool TcpClient =
TcpConnectionPool (Internal.ConnectionPool HandlerParams Socket SockAddr)
deriving (Generic, Show)
instance
HasConnectionPool HandlerParams Socket SockAddr (ConnectionPool TcpClient)
where
connectionPool = const TcpConnectionPool <^@~ \(TcpConnectionPool a) -> a
instance ConnectionPoolFor TcpClient where
type HandlerData TcpClient = AppData
withConnection = withTcpClientConnection
tryWithConnection = tryWithTcpClientConnection
destroyAllConnections = destroyAllTcpClientConnections
createTcpClientPool
:: ResourcePoolParams
-> ClientSettings
-> IO (ConnectionPool TcpClient)
createTcpClientPool poolParams tcpParams = TcpConnectionPool
<$> Internal.createConnectionPool handlerParams acquire release poolParams
where
acquire = Internal.acquireTcpClientConnection tcpParams
release = Internal.close
handlerParams = Internal.fromClientSettings tcpParams
withTcpClientConnection
:: (MonadBaseControl io m, io ~ IO)
=> ConnectionPool TcpClient
-> (AppData -> m r)
-> m r
withTcpClientConnection (TcpConnectionPool pool) =
Internal.withConnection pool . Internal.runTcpApp Nothing
tryWithTcpClientConnection
:: (MonadBaseControl io m, io ~ IO)
=> ConnectionPool TcpClient
-> (AppData -> m r)
-> m (Maybe r)
tryWithTcpClientConnection (TcpConnectionPool pool) =
Internal.tryWithConnection pool . Internal.runTcpApp Nothing
destroyAllTcpClientConnections
:: ConnectionPool TcpClient
-> IO ()
destroyAllTcpClientConnections (TcpConnectionPool pool) =
Internal.destroyAllConnections pool