squeal-postgresql-0.3.1.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2017
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Pool

Contents

Description

A MonadPQ for pooled connections.

Synopsis

Pools

newtype PoolPQ (schema :: SchemaType) m x Source #

PoolPQ schema should be a drop-in replacement for PQ schema schema.

Constructors

PoolPQ 

Fields

Instances
MonadBase b m => MonadBase b (PoolPQ schema m) Source #

MonadBase instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

liftBase :: b α -> PoolPQ schema m α #

MonadBaseControl b m => MonadBaseControl b (PoolPQ schema m) Source #

MonadBaseControl instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Associated Types

type StM (PoolPQ schema m) a :: * #

Methods

liftBaseWith :: (RunInBase (PoolPQ schema m) b -> b a) -> PoolPQ schema m a #

restoreM :: StM (PoolPQ schema m) a -> PoolPQ schema m a #

MonadBaseControl IO io => MonadPQ schema (PoolPQ schema io) Source #

MonadPQ instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

manipulateParams :: ToParams x params => Manipulation schema params ys -> x -> PoolPQ schema io (K Result ys) Source #

manipulate :: Manipulation schema [] ys -> PoolPQ schema io (K Result ys) Source #

runQueryParams :: ToParams x params => Query schema params ys -> x -> PoolPQ schema io (K Result ys) Source #

runQuery :: Query schema [] ys -> PoolPQ schema io (K Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation schema params ys -> list x -> PoolPQ schema io (list (K Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation schema params ys -> PoolPQ schema io (list (K Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation schema params [] -> list x -> PoolPQ schema io () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation schema params [] -> PoolPQ schema io () Source #

liftPQ :: (Connection -> IO a) -> PoolPQ schema io a Source #

MonadTrans (PoolPQ schema :: (* -> *) -> * -> *) Source #

MonadTrans instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

lift :: Monad m => m a -> PoolPQ schema m a #

Monad m => Monad (PoolPQ schema m) Source #

Monad instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

(>>=) :: PoolPQ schema m a -> (a -> PoolPQ schema m b) -> PoolPQ schema m b #

(>>) :: PoolPQ schema m a -> PoolPQ schema m b -> PoolPQ schema m b #

return :: a -> PoolPQ schema m a #

fail :: String -> PoolPQ schema m a #

Functor m => Functor (PoolPQ schema m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

fmap :: (a -> b) -> PoolPQ schema m a -> PoolPQ schema m b #

(<$) :: a -> PoolPQ schema m b -> PoolPQ schema m a #

Monad m => Applicative (PoolPQ schema m) Source #

Applicative instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

pure :: a -> PoolPQ schema m a #

(<*>) :: PoolPQ schema m (a -> b) -> PoolPQ schema m a -> PoolPQ schema m b #

liftA2 :: (a -> b -> c) -> PoolPQ schema m a -> PoolPQ schema m b -> PoolPQ schema m c #

(*>) :: PoolPQ schema m a -> PoolPQ schema m b -> PoolPQ schema m b #

(<*) :: PoolPQ schema m a -> PoolPQ schema m b -> PoolPQ schema m a #

type StM (PoolPQ schema m) x Source # 
Instance details

Defined in Squeal.PostgreSQL.Pool

type StM (PoolPQ schema m) x = StM m x

createConnectionPool Source #

Arguments

:: MonadBase IO io 
=> ByteString

The passed string can be empty to use all default parameters, or it can contain one or more parameter settings separated by whitespace. Each parameter setting is in the form keyword = value. Spaces around the equal sign are optional. To write an empty value or a value containing spaces, surround it with single quotes, e.g., keyword = 'a value'. Single quotes and backslashes within the value must be escaped with a backslash, i.e., ' and .

-> Int

The number of stripes (distinct sub-pools) to maintain. The smallest acceptable value is 1.

-> NominalDiffTime

Amount of time for which an unused connection is kept open. The smallest acceptable value is 0.5 seconds. The elapsed time before destroying a connection may be a little longer than requested, as the reaper thread wakes at 1-second intervals.

-> Int

Maximum number of connections to keep open per stripe. The smallest acceptable value is 1. Requests for connections will block if this limit is reached on a single stripe, even if other stripes have idle connections available.

-> io (Pool (K Connection schema)) 

Create a striped pool of connections. Although the garbage collector will destroy all idle connections when the pool is garbage collected it's recommended to manually destroyAllResources when you're done with the pool so that the connections are freed up as soon as possible.

data Pool a #

Instances
Show (Pool a) 
Instance details

Defined in Data.Pool

Methods

showsPrec :: Int -> Pool a -> ShowS #

show :: Pool a -> String #

showList :: [Pool a] -> ShowS #

destroyAllResources :: Pool a -> IO () #

Destroy all resources in all stripes in the pool. Note that this will ignore any exceptions in the destroy function.

This function is useful when you detect that all resources in the pool are broken. For example after a database has been restarted all connections opened before the restart will be broken. In that case it's better to close those connections so that takeResource won't take a broken connection from the pool but will open a new connection instead.

Another use-case for this function is that when you know you are done with the pool you can destroy all idle resources immediately instead of waiting on the garbage collector to destroy them, thus freeing up those resources sooner.

type PoolPQRun schema = forall m x. Monad m => PoolPQ schema m x -> m x Source #

A snapshot of the state of a PoolPQ computation.

poolpqliftWith :: Functor m => (PoolPQRun schema -> m a) -> PoolPQ schema m a Source #

Helper function in defining MonadBaseControl instance for PoolPQ.